-- vim: set tabstop=2 softtabstop=0 expandtab shiftwidth=2: module Exercise06 where import Data.List import Effects import Types sinPeriod :: Signal sinPeriod s = sin $ s*2.0*pi sqwPeriod :: Signal sqwPeriod s | s < 0.5 = -1 | otherwise = 1 sawPeriod :: Signal sawPeriod s = s * 2 - 1 triPeriod :: Signal triPeriod s | s < 0.5 = s * 4 - 1 | otherwise = (0.5 - s) * 4 + 1 silence :: Signal silence = const 0.0 -- NOTE: the formula is taken from https://pages.mtu.edu/~suits/NoteFreqCalcs.html semitoneHz :: Semitone -> Hz semitoneHz n = 440.0 * (2 ** (fromInteger n / 12.0)) osc :: Signal -> ADSR -> Oscillator osc signal pAdsr semitone duration = adsr pAdsr duration (\t -> let hz = semitoneHz semitone in let thz = t * hz in let t' = thz - fromInteger (floor thz) in signal t') adsr :: ADSR -> Seconds -> Signal -> Signal adsr (a,d,v_s,r) duration signal = f where td = a + d ts = td + duration - (a + d + r) f t | t < a = (t / a) * signal t | t < td = let t' = t - a in (v_s + (1 - t' / d) * (1 - v_s)) * signal t | t < ts = v_s * signal t | t < duration = let t' = t - ts in (1 - t' / r) * v_s * signal t | otherwise = 0.0 mix :: [SampledSignal] -> SampledSignal mix [] = [0.0] mix [sig] = sig mix signals = (/(fromIntegral $ length signals)) <$> foldl1 (zipWith (+)) (extendLength <$> signals) where maxSamples = maximum $ length <$> signals extendLength s = if length s < maxSamples then s ++ repeat 0 else s --mix signals = tanh <$> foldl1 (zipWith (+)) (extendLength <$> signals) -- where -- maxSamples = maximum $ length <$> signals -- extendLength s = if length s < maxSamples then s ++ repeat 0 else s {-WETT-} {-MCCOMMENT To generate the desired output please use: stack run -- mid/malte_comp_for_fpv.mid out.wav HINT: Due to the long midi and more complicated functions, generation time is around 2 minutes on my computer. If this is too long for you, disable the reverb effect below. If you do not intend to apply the given fix below, please fall back to using song of storms. I wanted to try a different approach and focus on creating a piano sound, for which I composed a midi file. But unfortunately the template disliked it ("Wrong format"), probably because of some midi control messages that my music program exported. Also unfortunately, my approach of applying FIR (Finite Impule Response) filters has not worked out as well as I hoped, because convolution in haskell is unbearably slow, and speeding it up properly would only work with extra packages to do parallelism or stream fusion, which we may not use. And I didn't want to convert all the code to arrays, because then I would have had to reimplement the whole template :/ . (although the original great hall impulse response would sound great, if you can spare the 2 hours it takes until it is has finally finished calculating) The fix I used to be able to convert the file is to ignore other messages by applying the following diff to line 40 in Synth.hs: - | otherwise = error "Wrong MIDI-Format" + | otherwise = format xs -} semitoneHzFrac :: Double -> Hz semitoneHzFrac n = 440.0 * (2 ** (n / 12.0)) -- you can add new oscillators here piano :: Oscillator piano = osc sawPeriod (0.01, 0.1, 0.7, 0.2) lead :: Oscillator lead = osc sqwPeriod (0.01, 0.2, 0.3, 0.1) bass :: Oscillator bass = osc sinPeriod (0.001, 0.2, 0.9, 0.1) better_adsr :: ADSR -> Seconds -> Signal -> Signal better_adsr (attack,decay,sustainVol,release) duration signal = \t -> tanh((5/attack)*t) -- Attack envelope * (sustainVol+(1-sustainVol) -- Sustain volume modifier * exp(-((2/decay)*(t-attack))**2)) -- Exponential decay in sustain * exp(-(1/s)*t) -- Gradual decay * 0.5 * (1+tanh(-((2/release) * (t-(max 1.0 duration)+release)))) -- Faster release towards duration * signal t -- Signal where s = duration --sem0 = semitoneHz 0 --sem24 = semitoneHz 24 --semm24 = semitoneHz (-24) -- --very_good_piano :: Double -> Signal --very_good_piano hz t = if i <= snd (Array.bounds lemap) then lemap Array.! i else 0.0 -- where i = floor (t * hz / basefac * 48000) -- (lemap, basefac) = if hz < sem0 then (vgpm24,semm24) else -- if hz < sem24 then (vgp,sem0) else -- (vgp24,sem24) -- Original equation from: https://dsp.stackexchange.com/questions/46598/mathematical-equation-for-the-sound-wave-that-a-piano-makes -- With slight modifications better_piano :: Double -> Signal better_piano frequency time = z -- * (1 + 16 * time * exp(-6 * time)) where z = y + (y * y * y) y = 0.8 * sin( 2 * pft) * exp(-0.0004 * 2 * pft) + 0.8 * sin(2 * 2 * pft) * exp(-0.0004 * 2 * pft) / 2 + 0.8 * sin(3 * 2 * pft) * exp(-0.0004 * 2 * pft) / 4 + 0.8 * sin(4 * 2 * pft) * exp(-0.0004 * 2 * pft) / 8 + 0.8 * sin(5 * 2 * pft) * exp(-0.0004 * 2 * pft) / 16 + 0.8 * sin(6 * 2 * pft) * exp(-0.0004 * 2 * pft) / 32 pft = pi * frequency * time better_osc :: (Double -> Signal) -> ADSR -> Double -> Seconds -> Double -> Double better_osc freq_signal pAdsr semitone duration = better_adsr pAdsr duration (\t -> freq_signal (semitoneHzFrac semitone) t) organPeriod :: Signal organPeriod x = let t = x*2.0*pi in sin(t) + 1/2*cos(2*t) + 1/4*sin(4*t) + 1/8*cos(8*t) -- Mix some near frequencies for more depth piano_good :: Oscillator piano_good semitone duration = (\t -> 1/3 * ( better_osc better_piano (0.03, 0.5, 0.1, 0.02) (fromInteger semitone) duration t + 1/2 * better_osc better_piano (0.03, 0.2, 0.02, 0.02) (fromInteger semitone+0.1) duration t -- + 1/4 * better_osc better_piano (0.03, 0.18, 0.01, 0.02) (fromInteger semitone-0.1) duration t )) -- mix the signals with some volume mixTracks :: [SampledSignal] -> [Double] -> SampledSignal mixTracks trks vols = mix $ zipWith (\trk vol -> map (* vol) trk) trks vols -- Do not clip notes after duration, but let the oscillator fade them out playNotes' :: Oscillator -> [Note] -> SampledSignal playNotes' _ [] = [] playNotes' osc notes = reverse $ map (/ fromIntegral n) sampledSig where (n, _, _, sampledSig) = foldl' h (0, [], notes, []) [0..samplesPerSecond $ endTime $ last notes] endTime (_, start, duration) = start + (max 1.0 duration) startTime (_, start, _) = start osc' (tone, _, duration) = osc tone duration h (n, [], [], xs) i = (n, [], [], 0:xs) h (n, sigs, notes, xs) i = let t = fromIntegral i / sampleRate (nextNotes, notes') = break (\note -> startTime note > t) notes sigs' = map (\note -> (osc' note . (\t -> t - startTime note), endTime note)) nextNotes ++ filter (\(_, end) -> t <= end) sigs n' = max n $ length sigs' sample = sum (map (($ t) . fst) sigs') in (n', sigs', notes', sample:xs) -- From: https://jip.dev/posts/naive-convolution-in-haskell/ convolve :: (Num a) => [a] -> [a] -> [a] convolve hs xs = map (sum' . zipWith (*) (reverse' hs)) (init $ tails ts) where sum' = foldl' (+) 0 reverse' = foldl' (flip (:)) [] pad = replicate ((length hs) - 1) 0 ts = pad ++ xs -- From: https://www.openair.hosted.york.ac.uk/?page_id=406 --originalGreatHall = read "[-0.00009448,-0.00018896,0.00000000,-0.00018896,0.00004724,-0.00037791,-0.00009448,0.00000000,-0.00028343,0.00014172,-0.00037791,-0.00014172,0.00000000,-0.00018896,0.00000000,-0.00028343,0.00000000,-0.00009448,-0.00009448,-0.00018896,-0.00014172,-0.00009448,-0.00009448,0.00000000,-0.00028343,0.00018896,-0.00042515,0.00037791,-0.00051963,0.00037791,-0.00042515,0.00023620,-0.00037791,0.00014172,-0.00033067,0.00000000,0.00004724,-0.00009448,-0.00009448,0.00004724,-0.00028343,0.00023620,-0.00023620,-0.00023620,0.00000000,-0.00004724,-0.00023620,0.00014172,-0.00037791,0.00014172,-0.00014172,-0.00004724,-0.00023620,0.00004724,-0.00033067,0.00009448,-0.00023620,0.00000000,-0.00033067,-0.00004724,-0.00009448,-0.00023620,0.00014172,-0.00047239,0.00018896,-0.00028343,0.00000000,-0.00033067,-0.00004724,-0.00023620,-0.00004724,-0.00018896,-0.00009448,-0.00014172,-0.00014172,-0.00009448,-0.00028343,0.00004724,-0.00051963,0.00000000,-0.00033067,-0.00009448,-0.00009448,-0.00023620,-0.00009448,0.00004724,-0.00047239,0.00028343,-0.00047239,0.00014172,-0.00009448,-0.00037791,0.00014172,-0.00047239,0.00014172,-0.00028343,-0.00018896,-0.00014172,-0.00014172,-0.00018896,-0.00009448,-0.00023620,-0.00037791,0.00014172,-0.00056687,-0.00004724,-0.00042515,-0.00028343,-0.00009448,-0.00028343,-0.00033067,-0.00018896,-0.00037791,-0.00023620,-0.00009448,-0.00051963,-0.00009448,-0.00028343,-0.00018896,-0.00014172,-0.00033067,-0.00033067,-0.00004724,-0.00033067,-0.00004724,-0.00033067,-0.00018896,-0.00018896,-0.00009448,-0.00028343,-0.00023620,-0.00009448,-0.00028343,-0.00009448,-0.00009448,-0.00047239,0.00009448,-0.00047239,0.00004724,-0.00047239,-0.00014172,-0.00023620,-0.00037791,0.00014172,-0.00056687,0.00000000,-0.00033067,-0.00023620,-0.00004724,-0.00051963,0.00009448,-0.00051963,0.00014172,-0.00042515,0.00014172,-0.00047239,0.00000000,-0.00023620,-0.00014172,-0.00033067,0.00000000,-0.00023620,-0.00023620,-0.00004724,-0.00037791,-0.00018896,-0.00009448,-0.00037791,0.00004724,-0.00051963,0.00000000,-0.00037791,-0.00018896,-0.00014172,-0.00047239,0.00000000,-0.00023620,-0.00033067,0.00000000,-0.00051963,0.00023620,-0.00042515,0.00004724,-0.00033067,-0.00033067,0.00018896,-0.00056687,0.00009448,-0.00033067,-0.00014172,0.00000000,-0.00018896,-0.00023620,-0.00028343,0.00000000,-0.00037791,0.00009448,-0.00042515,-0.00009448,-0.00018896,-0.00028343,0.00000000,-0.00047239,0.00009448,-0.00047239,0.00000000,-0.00037791,-0.00018896,-0.00028343,-0.00009448,-0.00028343,-0.00023620,-0.00023620,-0.00033067,-0.00004724,-0.00042515,-0.00004724,-0.00061411,0.00014172,-0.00047239,-0.00014172,-0.00023620,-0.00037791,0.00000000,-0.00028343,-0.00014172,-0.00028343,-0.00037791,-0.00004724,-0.00033067,0.00009448,-0.00066135,0.00004724,-0.00051963,0.00000000,-0.00028343,-0.00023620,-0.00023620,-0.00004724,-0.00047239,0.00004724,-0.00056687,-0.00004724,-0.00028343,-0.00037791,-0.00004724,-0.00037791,-0.00004724,-0.00028343,-0.00023620,-0.00033067,-0.00037791,0.00000000,-0.00061411,0.00037791,-0.00085030,0.00037791,-0.00066135,0.00014172,-0.00033067,-0.00028343,-0.00009448,-0.00037791,0.00000000,-0.00051963,0.00000000,-0.00042515,-0.00009448,-0.00023620,-0.00047239,0.00000000,-0.00042515,-0.00009448,-0.00023620,-0.00051963,0.00000000,-0.00047239,0.00004724,-0.00047239,-0.00014172,-0.00037791,-0.00004724,-0.00033067,-0.00009448,-0.00033067,-0.00018896,-0.00009448,-0.00023620,-0.00023620,-0.00018896,-0.00033067,0.00014172,-0.00051963,0.00000000,-0.00033067,-0.00033067,0.00018896,-0.00047239,-0.00004724,-0.00018896,-0.00018896,-0.00023620,0.00004724,-0.00051963,0.00009448,-0.00028343,-0.00009448,-0.00004724,-0.00037791,-0.00004724,-0.00028343,0.00000000,-0.00028343,-0.00014172,-0.00023620,-0.00023620,-0.00009448,-0.00037791,-0.00004724,-0.00037791,0.00014172,-0.00047239,0.00004724,-0.00042515,0.00000000,-0.00023620,-0.00009448,-0.00033067,-0.00014172,-0.00009448,-0.00014172,-0.00037791,-0.00009448,-0.00037791,0.00000000,-0.00023620,-0.00028343,-0.00028343,-0.00018896,-0.00028343,-0.00009448,-0.00033067,-0.00037791,0.00009448,-0.00051963,-0.00009448,-0.00014172,-0.00061411,0.00009448,-0.00033067,-0.00033067,-0.00004724,-0.00051963,-0.00023620,-0.00014172,-0.00042515,-0.00033067,-0.00014172,-0.00037791,-0.00004724,-0.00042515,-0.00028343,-0.00028343,-0.00004724,-0.00047239,-0.00004724,-0.00056687,0.00004724,-0.00023620,-0.00023620,-0.00018896,-0.00056687,0.00004724,-0.00033067,-0.00023620,-0.00028343,-0.00028343,-0.00018896,-0.00023620,-0.00023620,-0.00028343,-0.00042515,0.00014172,-0.00051963,0.00009448,-0.00056687,0.00004724,-0.00037791,0.00004724,-0.00047239,-0.00018896,-0.00042515,0.00000000,-0.00042515,0.00004724,-0.00056687,0.00014172,-0.00042515,-0.00018896,-0.00018896,-0.00033067,-0.00004724,-0.00033067,-0.00023620,-0.00037791,-0.00009448,-0.00047239,0.00004724,-0.00047239,-0.00014172,-0.00028343,-0.00018896,-0.00014172,-0.00037791,-0.00014172,-0.00042515,-0.00009448,-0.00028343,-0.00033067,-0.00014172,-0.00047239,0.00000000,-0.00047239,-0.00018896,-0.00042515,-0.00023620,-0.00033067,-0.00028343,-0.00009448,-0.00056687,-0.00004724,-0.00047239,-0.00014172,-0.00037791,-0.00037791,-0.00023620,-0.00023620,-0.00042515,-0.00018896,-0.00047239,-0.00028343,-0.00004724,-0.00066135,-0.00014172,-0.00037791,-0.00037791,0.00000000,-0.00070859,0.00009448,-0.00070859,0.00009448,-0.00047239,-0.00023620,-0.00033067,-0.00028343,-0.00023620,-0.00023620,-0.00047239,-0.00023620,-0.00028343,-0.00009448,-0.00051963,0.00009448,-0.00080307,0.00037791,-0.00066135,-0.00014172,-0.00037791,-0.00023620,-0.00033067,-0.00014172,-0.00047239,-0.00028343,-0.00023620,-0.00033067,-0.00023620,-0.00033067,-0.00028343,-0.00028343,-0.00009448,-0.00037791,-0.00033067,-0.00009448,-0.00047239,0.00014172,-0.00047239,-0.00014172,-0.00028343,-0.00004724,-0.00033067,-0.00018896,-0.00028343,-0.00028343,-0.00004724,-0.00028343,-0.00018896,-0.00033067,-0.00014172,-0.00009448,-0.00033067,0.00000000,-0.00066135,0.00023620,-0.00056687,-0.00004724,-0.00028343,-0.00042515,0.00000000,-0.00033067,-0.00018896,-0.00033067,-0.00014172,-0.00014172,-0.00028343,0.00004724,-0.00070859,0.00028343,-0.00056687,0.00014172,-0.00051963,-0.00009448,-0.00037791,-0.00004724,-0.00042515,-0.00009448,-0.00037791,-0.00009448,-0.00023620,-0.00014172,-0.00028343,-0.00014172,-0.00018896,-0.00023620,-0.00004724,-0.00047239,0.00009448,-0.00056687,0.00018896,-0.00047239,-0.00018896,-0.00028343,-0.00014172,-0.00033067,-0.00009448,-0.00051963,0.00000000,-0.00033067,-0.00004724,-0.00037791,-0.00018896,-0.00018896,-0.00014172,-0.00028343,-0.00023620,-0.00037791,-0.00009448,-0.00018896,-0.00009448,-0.00033067,-0.00018896,-0.00023620,0.00000000,-0.00028343,-0.00004724,-0.00033067,-0.00014172,-0.00009448,-0.00023620,-0.00004724,-0.00018896,-0.00009448,0.00000000,-0.00033067,0.00009448,-0.00028343,0.00009448,-0.00028343,-0.00004724,-0.00033067,-0.00004724,-0.00004724,-0.00023620,-0.00004724,-0.00037791,0.00014172,-0.00023620,0.00009448,-0.00033067,0.00000000,0.00000000,-0.00004724,0.00000000,-0.00033067,0.00009448,-0.00009448,0.00004724,-0.00018896,-0.00014172,-0.00009448,0.00000000,-0.00004724,0.00000000,-0.00014172,-0.00018896,0.00009448,-0.00014172,-0.00009448,-0.00004724,-0.00014172,0.00009448,-0.00014172,-0.00009448,-0.00009448,0.00004724,0.00000000,-0.00023620,0.00000000,-0.00023620,0.00009448,-0.00014172,-0.00004724,-0.00037791,0.00014172,-0.00033067,0.00037791,-0.00042515,0.00000000,-0.00028343,0.00000000,-0.00014172,-0.00014172,-0.00028343,-0.00009448,0.00004724,-0.00014172,-0.00004724,-0.00009448,-0.00033067,0.00023620,-0.00023620,-0.00014172,0.00004724,-0.00018896,0.00014172,-0.00023620,-0.00014172,0.00000000,-0.00018896,0.00023620,-0.00042515,0.00028343,-0.00056687,0.00042515,-0.00042515,0.00004724,-0.00018896,-0.00023620,0.00000000,0.00004724,-0.00028343,-0.00009448,-0.00009448,-0.00018896,0.00004724,-0.00042515,-0.00009448,-0.00014172,0.00004724,-0.00023620,-0.00009448,-0.00028343,-0.00028343,0.00023620,-0.00051963,0.00014172,-0.00037791,0.00004724,-0.00023620,-0.00028343,-0.00014172,-0.00033067,0.00004724,-0.00033067,-0.00009448,-0.00033067,0.00004724,-0.00037791,0.00018896,-0.00061411,0.00014172,-0.00033067,0.00004724,-0.00033067,-0.00014172,-0.00018896,-0.00018896,0.00009448,-0.00051963,0.00000000,-0.00028343,0.00004724,-0.00014172,-0.00014172,-0.00023620,-0.00014172,0.00000000,-0.00023620,-0.00004724,-0.00037791,-0.00004724,-0.00009448,-0.00004724,-0.00033067,0.00000000,-0.00047239,0.00028343,-0.00033067,-0.00004724,-0.00033067,0.00000000,-0.00018896,0.00004724,-0.00014172,-0.00023620,-0.00004724,0.00000000,-0.00023620,-0.00018896,-0.00014172,-0.00004724,-0.00014172,-0.00004724,-0.00042515,0.00000000,-0.00018896,0.00004724,-0.00028343,0.00004724,-0.00028343,0.00004724,-0.00014172,-0.00028343,0.00009448,-0.00056687,0.00028343,-0.00033067,-0.00009448,-0.00009448,-0.00028343,0.00009448,-0.00014172,-0.00014172,-0.00037791,0.00018896,-0.00056687,0.00014172,-0.00028343,-0.00014172,-0.00023620,0.00018896,-0.00066135,0.00042515,-0.00066135,0.00023620,-0.00028343,-0.00018896,-0.00018896,-0.00009448,-0.00018896,0.00000000,-0.00037791,-0.00004724,-0.00018896,0.00014172,-0.00028343,0.00009448,-0.00037791,0.00028343,-0.00056687,0.00047239,-0.00061411,0.00004724,-0.00004724,-0.00023620,0.00009448,-0.00023620,-0.00009448,-0.00004724,-0.00004724,-0.00028343,-0.00023620,0.00000000,-0.00037791,0.00033067,-0.00056687,0.00018896,-0.00037791,0.00000000,-0.00018896,-0.00028343,0.00004724,-0.00051963,0.00037791,-0.00066135,0.00018896,-0.00051963,0.00009448,-0.00018896,-0.00018896,-0.00009448,-0.00014172,-0.00018896,0.00000000,-0.00037791,-0.00009448,-0.00023620,-0.00033067,0.00023620,-0.00070859,0.00018896,-0.00042515,-0.00009448,-0.00014172,-0.00033067,-0.00033067,-0.00009448,-0.00004724,-0.00033067,0.00004724,-0.00037791,-0.00009448,-0.00004724,-0.00033067,-0.00033067,0.00000000,-0.00033067,0.00014172,-0.00033067,-0.00023620,-0.00004724,-0.00023620,0.00000000,-0.00042515,-0.00004724,-0.00023620,-0.00014172,0.00000000,-0.00042515,-0.00014172,-0.00004724,-0.00028343,-0.00004724,-0.00033067,-0.00023620,-0.00004724,-0.00009448,-0.00028343,-0.00014172,-0.00023620,-0.00028343,0.00014172,-0.00047239,-0.00014172,-0.00023620,-0.00018896,0.00014172,-0.00037791,-0.00028343,-0.00004724,-0.00037791,0.00018896,-0.00047239,-0.00014172,-0.00014172,-0.00009448,0.00000000,-0.00033067,-0.00028343,-0.00004724,-0.00042515,0.00014172,-0.00047239,-0.00023620,-0.00004724,-0.00018896,-0.00014172,-0.00028343,-0.00023620,-0.00014172,0.00000000,-0.00042515,0.00000000,-0.00061411,0.00023620,-0.00047239,0.00004724,-0.00028343,-0.00033067,0.00014172,-0.00028343,0.00004724,-0.00056687,0.00014172,-0.00047239,0.00018896,-0.00051963,-0.00018896,-0.00009448,-0.00018896,0.00000000,-0.00037791,-0.00014172,-0.00004724,-0.00018896,-0.00014172,-0.00023620,-0.00028343,-0.00018896,0.00009448,-0.00042515,0.00009448,-0.00051963,0.00023620,-0.00028343,0.00004724,-0.00033067,-0.00009448,-0.00009448,0.00000000,-0.00042515,0.00009448,-0.00051963,0.00028343,-0.00028343,0.00004724,-0.00028343,0.00000000,-0.00014172,0.00009448,-0.00023620,-0.00014172,0.00000000,-0.00004724,0.00009448,-0.00033067,-0.00004724,0.00004724,-0.00009448,0.00004724,-0.00018896,-0.00014172,0.00009448,-0.00004724,-0.00004724,-0.00009448,-0.00004724,0.00014172,-0.00018896,0.00014172,-0.00028343,0.00004724,0.00018896,-0.00018896,0.00004724,-0.00009448,-0.00014172,0.00042515,-0.00033067,0.00018896,-0.00009448,0.00009448,0.00018896,-0.00009448,-0.00004724,-0.00023620,0.00037791,-0.00014172,0.00014172,-0.00004724,-0.00014172,0.00014172,0.00018896,-0.00004724,0.00000000,-0.00004724,0.00000000,0.00014172,-0.00014172,0.00000000,0.00004724,0.00000000,0.00014172,-0.00023620,0.00004724,-0.00014172,0.00018896,-0.00014172,0.00000000,-0.00014172,0.00004724,0.00014172,-0.00009448,0.00009448,-0.00023620,0.00028343,-0.00023620,0.00018896,-0.00023620,0.00004724,-0.00004724,0.00023620,-0.00033067,0.00023620,-0.00018896,0.00004724,0.00018896,-0.00028343,-0.00004724,0.00009448,-0.00023620,0.00037791,-0.00047239,0.00028343,-0.00037791,0.00042515,-0.00018896,0.00004724,0.00004724,-0.00014172,0.00014172,0.00014172,-0.00028343,0.00009448,0.00000000,0.00018896,-0.00009448,0.00014172,-0.00009448,0.00014172,0.00018896,-0.00009448,-0.00009448,0.00023620,-0.00028343,0.00033067,-0.00014172,0.00009448,-0.00004724,0.00033067,-0.00014172,0.00033067,-0.00037791,0.00042515,-0.00037791,0.00047239,-0.00042515,0.00023620,-0.00004724,0.00004724,0.00000000,0.00004724,-0.00028343,0.00028343,-0.00014172,0.00000000,-0.00004724,-0.00028343,0.00018896,-0.00009448,0.00000000,-0.00004724,-0.00028343,0.00037791,-0.00018896,0.00009448,0.00000000,-0.00004724,0.00018896,-0.00004724,-0.00018896,0.00009448,-0.00028343,0.00047239,-0.00014172,0.00004724,-0.00004724,0.00004724,0.00014172,0.00023620,-0.00018896,0.00004724,0.00009448,0.00023620,0.00004724,0.00000000,-0.00004724,0.00033067,0.00004724,0.00014172,-0.00018896,0.00009448,0.00014172,0.00004724,0.00000000,-0.00014172,0.00004724,0.00004724,0.00009448,0.00009448,-0.00014172,0.00018896,0.00000000,0.00028343,-0.00004724,-0.00009448,0.00023620,-0.00014172,0.00028343,-0.00023620,0.00014172,-0.00004724,0.00018896,0.00004724,-0.00009448,0.00000000,0.00004724,0.00014172,-0.00014172,0.00004724,-0.00018896,0.00018896,0.00014172,-0.00023620,0.00000000,-0.00018896,0.00028343,0.00004724,-0.00014172,0.00018896,-0.00028343,0.00033067,-0.00004724,-0.00014172,-0.00004724,0.00018896,-0.00014172,0.00042515,-0.00042515,0.00042515,-0.00033067,0.00051963,-0.00004724,-0.00009448,0.00023620,-0.00014172,0.00033067,-0.00009448,0.00004724,-0.00028343,0.00042515,-0.00018896,0.00056687,-0.00061411,0.00056687,-0.00033067,0.00047239,-0.00014172,-0.00004724,0.00009448,0.00014172,0.00004724,-0.00004724,-0.00004724,0.00000000,0.00037791,-0.00004724,0.00000000,-0.00014172,0.00023620,0.00009448,0.00014172,-0.00018896,0.00004724,0.00009448,0.00028343,-0.00004724,0.00004724,-0.00004724,0.00047239,-0.00009448,0.00033067,-0.00033067,0.00018896,-0.00004724,0.00028343,-0.00009448,0.00009448,0.00014172,0.00004724,0.00033067,0.00004724,-0.00018896,0.00033067,-0.00014172,0.00042515,-0.00037791,0.00018896,0.00000000,0.00028343,0.00004724,0.00009448,-0.00009448,0.00028343,0.00009448,0.00023620,-0.00014172,0.00009448,0.00009448,0.00014172,0.00004724,0.00004724,-0.00014172,0.00037791,0.00014172,0.00000000,-0.00004724,0.00014172,0.00028343,0.00014172,0.00014172,-0.00014172,0.00014172,0.00047239,-0.00009448,0.00037791,-0.00023620,0.00042515,-0.00004724,0.00051963,-0.00028343,0.00028343,0.00009448,0.00047239,0.00023620,-0.00009448,0.00037791,-0.00004724,0.00070859,-0.00018896,0.00037791,-0.00018896,0.00051963,0.00014172,0.00023620,0.00000000,0.00018896,0.00023620,0.00028343,0.00014172,0.00009448,0.00000000,0.00033067,0.00009448,0.00018896,0.00000000,0.00018896,0.00028343,0.00018896,0.00000000,0.00028343,0.00000000,0.00047239,-0.00014172,0.00033067,-0.00028343,0.00075583,-0.00018896,0.00056687,-0.00033067,0.00028343,0.00018896,0.00014172,0.00037791,-0.00037791,0.00047239,0.00000000,0.00023620,0.00023620,-0.00018896,0.00033067,0.00037791,0.00004724,0.00042515,-0.00028343,0.00051963,0.00000000,0.00042515,-0.00004724,0.00004724,0.00037791,0.00014172,0.00042515,-0.00004724,0.00000000,0.00037791,0.00009448,0.00033067,-0.00004724,0.00000000,0.00037791,0.00009448,0.00023620,0.00000000,0.00018896,0.00033067,0.00009448,0.00033067,-0.00033067,0.00056687,-0.00023620,0.00056687,-0.00028343,0.00033067,0.00000000,0.00042515,0.00028343,-0.00009448,0.00004724,0.00009448,0.00018896,0.00037791,-0.00042515,0.00056687,-0.00037791,0.00070859,-0.00009448,0.00000000,0.00033067,-0.00004724,0.00051963,-0.00004724,0.00004724,0.00004724,0.00009448,0.00033067,-0.00004724,0.00014172,0.00000000,0.00028343,0.00023620,0.00004724,0.00009448,0.00000000,0.00047239,-0.00023620,0.00033067,-0.00028343,0.00023620,0.00018896,0.00023620,-0.00009448,0.00000000,0.00023620,0.00018896,0.00018896,-0.00009448,0.00000000,0.00028343,0.00018896,0.00009448,-0.00018896,0.00009448,0.00018896,0.00033067,-0.00004724,0.00000000,-0.00014172,0.00047239,-0.00009448,0.00018896,-0.00028343,0.00018896,-0.00004724,0.00018896,0.00000000,-0.00028343,0.00028343,-0.00009448,0.00037791,-0.00037791,0.00033067,-0.00037791,0.00047239,0.00014172,-0.00037791,0.00023620,-0.00004724,0.00018896,0.00023620,-0.00028343,0.00009448,0.00014172,0.00009448,0.00009448,0.00000000,-0.00018896,0.00042515,0.00000000,0.00014172,-0.00009448,0.00004724,0.00014172,0.00028343,0.00000000,-0.00009448,0.00000000,0.00051963,-0.00009448,0.00033067,-0.00037791,0.00018896,0.00014172,0.00018896,-0.00009448,0.00000000,0.00023620,0.00014172,0.00037791,-0.00023620,0.00014172,0.00009448,0.00028343,0.00014172,-0.00018896,-0.00004724,0.00023620,0.00009448,0.00042515,-0.00037791,0.00037791,0.00028343,0.00018896,0.00018896,-0.00028343,0.00009448,0.00018896,0.00018896,0.00000000,-0.00004724,0.00028343,0.00037791,0.00023620,0.00009448,-0.00004724,0.00023620,0.00037791,0.00004724,0.00000000,-0.00004724,0.00014172,0.00037791,0.00014172,-0.00014172,0.00028343,0.00014172,0.00042515,0.00018896,-0.00037791,0.00028343,-0.00004724,0.00037791,0.00004724,-0.00004724,0.00014172,0.00033067,0.00023620,0.00028343,-0.00023620,0.00051963,0.00000000,0.00051963,-0.00023620,0.00000000,0.00023620,0.00018896,0.00047239,-0.00018896,0.00037791,0.00009448,0.00047239,0.00009448,-0.00009448,-0.00014172,0.00037791,0.00018896,0.00018896,0.00000000,-0.00004724,0.00037791,0.00042515,0.00009448,-0.00014172,0.00014172,0.00014172,0.00028343,0.00000000,-0.00014172,-0.00009448,0.00056687,0.00004724,0.00028343,-0.00033067,0.00042515,0.00004724,0.00051963,-0.00042515,0.00004724,-0.00004724,0.00037791,0.00033067,-0.00037791,0.00042515,-0.00042515,0.00094478,-0.00028343,0.00018896,-0.00014172,0.00009448,0.00042515,0.00009448,0.00000000,0.00014172,0.00018896,0.00042515,0.00023620,-0.00004724,0.00014172,0.00028343,0.00033067,0.00018896,-0.00014172,0.00033067,0.00018896,0.00051963,-0.00004724,0.00000000,0.00037791,0.00018896,0.00066135,-0.00014172,0.00009448,0.00023620,0.00042515,0.00037791,-0.00009448,0.00028343,-0.00009448,0.00080307,-0.00004724,-0.00009448,0.00009448,0.00018896,0.00042515,0.00023620,-0.00018896,0.00037791,0.00033067,0.00047239,0.00014172,-0.00009448,0.00028343,0.00033067,0.00033067,0.00004724,0.00004724,0.00028343,0.00066135,0.00033067,0.00028343,-0.00018896,0.00061411,0.00033067,0.00037791,0.00000000,-0.00009448,0.00042515,0.00037791,0.00042515,0.00018896,-0.00014172,0.00085030,0.00018896,0.00042515,-0.00004724,0.00000000,0.00042515,0.00066135,-0.00014172,0.00033067,-0.00009448,0.00056687,0.00085030,0.00009448,0.00037791,0.00014172,0.00051963,0.00075583,-0.00009448,0.00014172,0.00009448,0.00070859,0.00047239,0.00033067,-0.00004724,0.00056687,0.00037791,0.00080307,-0.00051963,0.00051963,-0.00018896,0.00075583,0.00037791,-0.00028343,0.00033067,0.00023620,0.00061411,0.00033067,-0.00014172,0.00014172,0.00023620,0.00042515,0.00000000,-0.00028343,0.00023620,0.00018896,0.00051963,0.00018896,-0.00018896,0.00023620,0.00033067,0.00033067,0.00004724,-0.00028343,0.00014172,0.00033067,0.00023620,-0.00014172,0.00004724,0.00009448,0.00089754,-0.00023620,0.00033067,-0.00056687,0.00075583,-0.00004724,0.00056687,-0.00075583,0.00037791,0.00000000,0.00080307,-0.00023620,0.00000000,0.00000000,0.00061411,0.00042515,0.00004724,-0.00023620,0.00023620,0.00051963,0.00056687,-0.00004724,0.00004724,0.00014172,0.00080307,0.00028343,0.00014172,-0.00028343,0.00051963,0.00051963,0.00033067,0.00004724,-0.00033067,0.00070859,0.00023620,0.00061411,-0.00042515,-0.00014172,0.00037791,0.00061411,0.00004724,0.00000000,-0.00037791,0.00066135,0.00075583,0.00004724,-0.00009448,-0.00014172,0.00056687,0.00061411,0.00000000,-0.00028343,0.00004724,0.00066135,0.00051963,0.00028343,-0.00028343,0.00028343,0.00047239,0.00075583,-0.00018896,0.00000000,0.00000000,0.00066135,0.00047239,0.00018896,-0.00009448,0.00061411,0.00075583,0.00047239,0.00000000,-0.00004724,0.00028343,0.00075583,0.00028343,0.00000000,0.00004724,0.00075583,0.00075583,0.00037791,0.00023620,0.00014172,0.00070859,0.00047239,-0.00009448,-0.00014172,0.00033067,0.00066135,0.00061411,0.00000000,0.00037791,0.00051963,0.00108650,0.00033067,-0.00014172,0.00004724,0.00042515,0.00070859,-0.00004724,-0.00004724,-0.00014172,0.00099202,0.00066135,0.00033067,-0.00066135,0.00042515,0.00042515,0.00085030,-0.00042515,-0.00051963,-0.00014172,0.00094478,0.00066135,-0.00014172,-0.00070859,0.00042515,0.00099202,0.00066135,-0.00033067,-0.00094478,0.00014172,0.00094478,0.00047239,-0.00061411,-0.00075583,0.00037791,0.00127546,0.00070859,-0.00047239,-0.00094478,0.00061411,0.00085030,0.00061411,-0.00089754,-0.00066135,0.00037791,0.00141717,0.00037791,-0.00037791,-0.00070859,0.00070859,0.00108650,0.00047239,-0.00099202,-0.00056687,0.00033067,0.00070859,0.00042515,-0.00075583,-0.00028343,0.00070859,0.00085030,0.00047239,0.00000000,-0.00028343,0.00085030,0.00018896,0.00051963,-0.00014172,0.00042515,0.00037791,0.00028343,0.00033067,0.00014172,0.00033067,-0.00004724,-0.00018896,-0.00004724,0.00070859,0.00051963,-0.00028343,-0.00094478,0.00023620,0.00099202,0.00118098,-0.00099202,-0.00136993,0.00004724,0.00193680,0.00127546,-0.00099202,-0.00193680,0.00061411,0.00316502,0.00160613,-0.00179509,-0.00335398,0.00042515,0.00325950,0.00198404,-0.00321226,-0.00410980,0.00122822,0.00472391,0.00302330,-0.00406257,-0.00486563,0.00122822,0.00614109,0.00264539,-0.00543250,-0.00614109,0.00207852,0.00845581,0.00377913,-0.00599937,-0.00722759,0.00321226,0.00977850,0.00335398,-0.00925887,-0.00968402,0.00273987,0.01190426,0.00349570,-0.01039261,-0.01010917,0.00604661,0.01539996,0.00453496,-0.01336868,-0.01275457,0.00675520,0.01705333,0.00335398,-0.01714781,-0.01459689,0.01053433,0.02286374,0.00491287,-0.02040731,-0.01648646,0.01218770,0.02574533,0.00118098,-0.02862692,-0.02087970,0.01738400,0.03420113,0.00420428,-0.03240605,-0.02239135,0.02390300,0.04029498,-0.00051963,-0.04558577,-0.02829624,0.03155574,0.05130170,-0.00448772,-0.05758451,-0.02706802,0.05413605,0.06750472,-0.02092694,-0.09249423,-0.02839072,0.09872979,0.09235251,-0.08252677,-0.16410875,0.12882112,0.66918959,0.90000000,0.36610330,-0.71704283,-1.54429456,-1.44868255,-0.54939114,0.38055847,0.68350304,0.39865106,0.07586605,0.11214571,0.37640143,0.48127231,0.28763909,0.03070544,-0.01710057,0.12490027,0.21252887,0.11587760,-0.04034222,-0.06207222,0.05295507,0.13184443,0.06093848,-0.07926727,-0.13264749,-0.07841696,-0.03798026,-0.10813038,-0.23364476,-0.28655259,-0.23133004,-0.15470817,-0.14790573,-0.19443628,-0.21748898,-0.18390195,-0.14299286,-0.14034747,-0.15607810,-0.14266219,-0.10510708,-0.10170586,-0.16132165,-0.23397544,-0.24087235,-0.17384002,-0.10208377,-0.09074638,-0.12641193,-0.14228427,-0.10515431,-0.04794772,-0.02111589,-0.02569809,-0.02220239,0.01851774,0.06944153,0.09197460,0.07293722,0.04336553,0.03250052,0.04185387,0.04893974,0.04194835,0.03056372,0.02810729,0.03935020,0.05394709,0.06698509,0.07572433,0.08210162,0.08304640,0.07652740,0.06457590,0.05092379,0.04090909,0.03816922,0.04534957,0.06089125,0.07090594,0.06419798,0.03585450,0.00179509,-0.01733676,-0.01436070,0.00146441,0.01563615,0.02040731,0.02206068,0.02173000,0.01908461,0.01147911,0.00491287,0.00684967,0.01856498,0.02900483,0.02994961,0.02399748,0.02097418,0.02829624,0.03760235,0.03731892,0.02328889,0.00401533,-0.00581041,-0.00340122,0.00963678,0.02191896,0.03330359,0.04501890,0.05942683,0.07340962,0.07950346,0.07369305,0.05862377,0.04431031,0.03490972,0.03240605,0.02942998,0.02475331,0.02295822,0.02824900,0.03968087,0.04808944,0.04605816,0.03727168,0.03131955,0.03174470,0.03382322,0.02810729,0.01766744,0.01124291,0.01832878,0.03302016,0.04322381,0.04374344,0.03873609,0.03901953,0.04497166,0.04889250,0.04374344,0.03443733,0.02862692,0.03396494,0.04298761,0.04898698,0.04808944,0.04360172,0.04374344,0.04601092,0.04780600,0.04322381,0.03472076,0.02938274,0.03311463,0.04615263,0.05678144,0.05758451,0.04520785,0.03226433,0.02905207,0.03840542,0.04671950,0.04426307,0.02957170,0.01842326,0.01799811,0.02480055,0.02338337,0.01053433,-0.00387361,-0.00406257,0.00769998,0.01813983,0.01327420,-0.00037791,-0.00897544,-0.00283435,0.00996746,0.01634474,0.01379383,0.00713311,0.00203128,-0.00396809,-0.01360487,-0.02196620,-0.02097418,-0.01034537,-0.00108650,-0.00141717,-0.01039261,-0.01899013,-0.02295822,-0.02593429,-0.02702079,-0.01894289,-0.00085030,0.00873924,-0.01058157,-0.04681398,-0.04374344,0.04912870,0.20960004,0.32845371,0.29288264,0.08871510,-0.16746273,-0.32235986,-0.30662923,-0.18040626,-0.05994646,-0.00949507,-0.00774722,0.00363741,0.04341277,0.08583351,0.09726538,0.08087340,0.05739555,0.03944468,0.01114844,-0.03387046,-0.08144027,-0.09821016,-0.07529918,-0.03864161,-0.02810729,-0.06235566,-0.12140458,-0.16973021,-0.18111484,-0.15503884,-0.10647701,-0.05923788,-0.02758765,-0.02144657,-0.03335083,-0.05252992,-0.06514277,-0.07100042,-0.07152005,-0.07444888,-0.07477955,-0.07062251,-0.05834033,-0.03958640,-0.01662818,0.00968402,0.03401218,0.04766429,0.04468822,0.02735146,0.00987298,0.00245644,0.00538526,0.01166807,0.01332144,0.01710057,0.02659563,0.04558577,0.06467038,0.07529918,0.07459059,0.06745748,0.05800966,0.04964833,0.04067290,0.03264224,0.02560361,0.02262755,0.02267478,0.02517846,0.02980789,0.03311463,0.03472076,0.03377598,0.03108335,0.02980789,0.02895759,0.02848520,0.02891035,0.03113059,0.03580726,0.03854713,0.03651585,0.02876863,0.02163552,0.01710057,0.01563615,0.01180978,0.00614109,0.00198404,0.00349570,0.00826685,0.01062881,0.00708587,0.00496011,0.00746378,0.01757296,0.02456435,0.02829624,0.02843796,0.03250052,0.03401218,0.02489502,-0.00094478,-0.02621772,-0.02966618,0.00155889,0.04922318,0.07912555,0.06637098,0.01516376,-0.04605816,-0.09003779,-0.10449297,-0.09499790,-0.06632375,-0.01988768,0.03883057,0.09551753,0.12409721,0.11299601,0.07133109,0.02857968,0.00477115,0.00141717,-0.00113374,-0.01384107,-0.02768213,-0.02390300,0.00510183,0.04109805,0.05517531,0.03500420,-0.00330674,-0.03387046,-0.03849990,-0.02716250,-0.01294352,-0.00354294,0.00864476,0.02895759,0.05215201,0.06315872,0.05692316,0.04138148,0.03127231,0.03226433,0.03632689,0.03453181,0.02664287,0.02224963,0.02810729,0.03712996,0.04067290,0.02994961,0.01620302,0.00784170,0.01015641,0.01558891,0.01360487,0.00604661,-0.00004724,0.00477115,0.01875394,0.03264224,0.03935020,0.03977535,0.04043670,0.04227903,0.04308209,0.03547659,0.02087970,0.00547974,-0.00316502,-0.00250367,0.00292883,0.00788894,0.00821961,0.00472391,0.00004724,-0.00349570,-0.00141717,0.00500735,0.01440794,0.02248583,0.02371405,0.02036007,0.01473861,0.01077052,0.01072328,0.00982574,0.00774722,0.00136993,-0.00401533,-0.00642452,-0.00188957,0.00500735,0.01048709,0.00850304,0.00132270,-0.00595213,-0.00788894,-0.00491287,-0.00118098,-0.00018896,0.00023620,0.00481839,0.01384107,0.02144657,0.02234411,0.01436070,0.00694415,0.00273987,0.00434600,0.00340122,-0.00009448,-0.00496011,-0.00477115,0.00018896,0.00481839,0.00524354,0.00212576,0.00188957,0.00581041,0.01303800,0.01544720,0.01341591,0.00661348,0.00255091,0.00094478,0.00392085,0.00765274,0.01091224,0.01072328,0.00585765,-0.00259815,-0.01081776,-0.01332144,-0.00845581,0.00165337,0.01006194,0.01067604,0.00188957,-0.01247113,-0.02503674,-0.02938274,-0.02645392,-0.01832878,-0.01039261,-0.00340122,0.00321226,0.00793617,0.00826685,0.00255091,-0.00510183,-0.00746378,-0.00255091,0.00245644,-0.00316502,-0.02248583,-0.04416859,-0.05309679,-0.04105081,-0.01762020,0.00481839,0.01346315,0.01147911,0.00061411,-0.01388831,-0.03136679,-0.04596368,-0.04969557,-0.03849990,-0.01984044,-0.00529078,-0.00354294,-0.01237665,-0.01984044,-0.02021835,-0.01289628,-0.00609385,-0.00359017,-0.00708587,-0.01256561,-0.01894289,-0.02513122,-0.03042200,-0.03183918,-0.02772937,-0.01809259,-0.00793617,-0.00222024,-0.00330674,-0.00925887,-0.01398278,-0.01379383,-0.00727483,-0.00028343,0.00505459,0.00363741,0.00014172,-0.00453496,-0.00675520,-0.00661348,-0.00666072,-0.00562146,-0.00769998,-0.01119567,-0.01521100,-0.01762020,-0.01511652,-0.01081776,-0.00859752,-0.01043985,-0.01232941,-0.00736931,0.00335398,0.01360487,0.01039261,-0.00222024,-0.01473861,-0.01454965,-0.00458220,-0.00108650,-0.01403002,-0.03585450,-0.04624711,-0.03287844,-0.00519630,0.01388831,0.01232941,-0.00165337,-0.00911715,-0.00141717,0.01251837,0.01714781,0.00973126,-0.00132270,-0.00193680,0.00557422,0.01351039,0.01091224,-0.00028343,-0.01209322,-0.01733676,-0.01539996,-0.01086500,-0.00840857,-0.00836133,-0.01039261,-0.01062881,-0.00755826,-0.00056687,0.00491287,0.00481839,-0.00557422,-0.01865946,-0.02772937,-0.02579257,-0.01615578,-0.00547974,0.00018896,0.00269263,0.00349570,0.00458220,0.00155889,-0.00675520,-0.02002939,-0.03188642,-0.03821646,-0.03755511,-0.03297292,-0.02730422,-0.02442263,-0.02281650,-0.02158828,-0.01832878,-0.01091224,-0.00585765,-0.00349570,-0.00954231,-0.01554168,-0.01813983,-0.01171531,-0.00170061,0.00661348,0.00760550,0.00250367,-0.00505459,-0.01077052,-0.01280181,-0.00836133,0.00023620,0.01081776,0.01625026,0.01327420,0.00472391,-0.00165337,-0.00122822,0.00585765,0.01025089,0.00831409,0.00103926,-0.00510183,-0.00647176,-0.00590489,-0.00784170,-0.01388831,-0.01899013,-0.01818707,-0.01143187,-0.00382637,-0.00004724,-0.00179509,-0.00429876,-0.00472391,-0.00581041,-0.00812513,-0.01544720,-0.02154105,-0.02300546,-0.01700609,-0.00727483,-0.00004724,0.00203128,-0.00269263,-0.01048709,-0.02210792,-0.03363426,-0.04232626,-0.04331829,-0.03339807,-0.01899013,-0.00547974,-0.00089754,-0.00259815,-0.00661348,-0.00793617,-0.00741654,-0.00755826,-0.00935335,-0.01058157,-0.00982574,-0.00727483,-0.00680244,-0.00845581,-0.01110120,-0.01176254,-0.01091224,-0.01143187,-0.01483309,-0.01936805,-0.02045455,-0.01601407,-0.00897544,-0.00481839,-0.00571594,-0.00845581,-0.00921163,-0.00472391,-0.00004724,0.00203128,-0.00141717,-0.00628280,-0.00840857,-0.00680244,-0.00396809,-0.00420428,-0.00713311,-0.01105396,-0.01062881,-0.00892820,-0.00666072,-0.00732207,-0.00869200,-0.00798341,-0.00330674,0.00099202,0.00302330,0.00047239,-0.00283435,-0.00359017,-0.00188957,0.00018896,-0.00004724,-0.00240920,-0.00410980,-0.00368465,-0.00217300,0.00028343,0.00245644,0.00439324,0.00609385,0.00382637,-0.00094478,-0.00614109,-0.00722759,-0.00066135,0.01043985,0.02059626,0.02380852,0.01899013,0.01039261,0.00151165,-0.00288159,-0.00599937,-0.00514907,-0.00359017,0.00094478,0.00552698,0.00732207,0.00524354,0.00023620,-0.00132270,0.00047239,0.00694415,0.00968402,0.00803065,0.00307054,0.00033067,0.00340122,0.00859752,0.01209322,0.00906991,0.00462944,0.00061411,0.00174785,0.00259815,0.00193680,-0.00420428,-0.01110120,-0.01799811,-0.02111589,-0.02229687,-0.02064350,-0.01705333,-0.01308524,-0.01209322,-0.01521100,-0.02291098,-0.02754042,-0.02763489,-0.02073798,-0.01549444,-0.01403002,-0.01922633,-0.02338337,-0.02409196,-0.01974596,-0.01629750,-0.01535272,-0.01733676,-0.01733676,-0.01483309,-0.01129015,-0.01058157,-0.01157359,-0.01228218,-0.00958954,-0.00765274,-0.00911715,-0.01643922,-0.02276926,-0.02182448,-0.01223494,0.00089754,0.00751102,0.00647176,-0.00108650,-0.00684967,-0.00845581,-0.00793617,-0.00694415,-0.00859752,-0.00892820,-0.00746378,-0.00307054,0.00184233,0.00547974,0.00722759,0.00708587,0.00462944,0.00127546,-0.00311778,-0.00491287,-0.00439324,-0.00231472,-0.00033067,-0.00066135,0.00000000,0.00165337,0.00590489,0.00755826,0.00647176,0.00122822,-0.00075583,-0.00023620,0.00401533,0.00311778,-0.00340122,-0.01322696,-0.01776191,-0.01374659,-0.00434600,0.00075583,-0.00259815,-0.01143187,-0.01780915,-0.01639198,-0.00949507,-0.00321226,-0.00188957,-0.00377913,-0.00448772,-0.00118098,0.00505459,0.00845581,0.00708587,0.00023620,-0.00831409,-0.01469137,-0.01799811,-0.01799811,-0.01587235,-0.01303800,-0.00911715,-0.00642452,-0.00623557,-0.00769998,-0.00992022,-0.00855028,-0.00623557,-0.00406257,-0.00769998,-0.01275457,-0.01705333,-0.01464413,-0.00992022,-0.00769998,-0.01095948,-0.01511652,-0.01379383,-0.00510183,0.00425152,0.00543250,-0.00118098,-0.01039261,-0.01308524,-0.00916439,-0.00382637,-0.00250367,-0.00552698,-0.00765274,-0.00703863,-0.00354294,-0.00075583,-0.00023620,-0.00066135,-0.00188957,-0.00207852,-0.00297607,-0.00198404,0.00028343,0.00453496,0.00807789,0.01006194,0.00935335,0.00812513,0.00614109,0.00529078,0.00354294,0.00288159,0.00245644,0.00236196,0.00363741,0.00382637,0.00382637,0.00231472,-0.00066135,-0.00325950,-0.00410980,-0.00288159,-0.00037791,0.00056687,0.00028343,-0.00066135,0.00113374,0.00245644,0.00377913,0.00051963,-0.00321226,-0.00604661,-0.00519630,-0.00392085,-0.00373189,-0.00566870,-0.00741654,-0.00722759,-0.00496011,-0.00344846,-0.00132270,0.00132270,0.00547974,0.00940059,0.00968402,0.00647176,0.00151165,-0.00278711,-0.00599937,-0.01025089,-0.01516376,-0.01743124,-0.01393554,-0.00467667,0.00538526,0.01025089,0.00817237,0.00307054,-0.00368465,-0.00689691,-0.01081776,-0.01384107,-0.01591959,-0.01554168,-0.01232941,-0.00855028,-0.00614109,-0.00491287,-0.00099202,0.00500735,0.01147911,0.01450241,0.01067604,0.00628280,0.00363741,0.00798341,0.01242389,0.01360487,0.00722759,-0.00099202,-0.00557422,-0.00278711,0.00325950,0.00670796,0.00547974,-0.00018896,-0.00462944,-0.00784170,-0.01043985,-0.01303800,-0.01601407,-0.01606131,-0.01384107,-0.01114844,-0.00982574,-0.01091224,-0.01006194,-0.00684967,-0.00085030,0.00359017,0.00396809,0.00141717,0.00075583,0.00335398,0.00987298,0.01303800,0.01157359,0.00547974,0.00056687,-0.00113374,0.00203128,0.00614109,0.00992022,0.01294352,0.01403002,0.01133739,0.00467667,-0.00410980,-0.00963678,-0.00873924,-0.00500735,-0.00170061,-0.00444048,-0.00831409,-0.01171531,-0.01072328,-0.00864476,-0.00633004,-0.00349570,0.00231472,0.00769998,0.00803065,-0.00269263,-0.01870670,-0.03122507,-0.02976066,-0.01676989,-0.00070859,0.00864476,0.00906991,0.00529078,0.00250367,0.00160613,0.00198404,0.00179509,0.00203128,0.00316502,0.00410980,0.00278711,0.00094478,-0.00217300,-0.00278711,-0.00410980,-0.00784170,-0.01327420,-0.01842326,-0.01658094,-0.00859752,0.00382637,0.01303800,0.01530548,0.01180978,0.00524354,-0.00033067,-0.00330674,-0.00599937,-0.00661348,-0.00656624,-0.00557422,-0.00439324,-0.00855028,-0.01445518,-0.02291098,-0.02418644,-0.01908461,-0.00718035,0.00354294,0.00902267,0.00836133,0.00311778,-0.00085030,-0.00481839,-0.00538526,-0.00486563,-0.00245644,0.00165337,0.00462944,0.00628280,0.00486563,0.00288159,0.00018896,-0.00184233,-0.00368465,-0.00581041,-0.00552698,-0.00453496,-0.00382637,-0.00661348,-0.01275457,-0.01941528,-0.02173000,-0.01762020,-0.01034537,-0.00439324,-0.00321226,-0.00599937,-0.00741654,-0.00566870,-0.00066135,0.00321226,0.00415704,0.00179509,0.00023620,0.00014172,0.00236196,0.00363741,0.00373189,0.00297607,0.00273987,0.00311778,0.00377913,0.00231472,0.00231472,0.00250367,0.00656624,0.01081776,0.01374659,0.01166807,0.00486563,-0.00505459,-0.01327420,-0.01865946,-0.01809259,-0.01464413,-0.00902267,-0.00425152,-0.00188957,-0.00051963,-0.00047239,0.00094478,0.00217300,0.00373189,0.00519630,0.00571594,0.00755826,0.00873924,0.01010917,0.00911715,0.00708587,0.00420428,0.00316502,0.00425152,0.00510183,0.00562146,0.00259815,0.00028343,-0.00108650,0.00023620,0.00146441,0.00028343,-0.00349570,-0.00708587,-0.00859752,-0.00656624,-0.00543250,-0.00571594,-0.00873924,-0.01114844,-0.01119567,-0.00958954,-0.00680244,-0.00491287,-0.00174785,0.00170061,0.00510183,0.00382637,0.00018896,-0.00373189,-0.00170061,0.00633004,0.01563615,0.01880118,0.01525824,0.00774722,0.00462944,0.00666072,0.01105396,0.01209322,0.00793617,0.00307054,-0.00014172,-0.00014172,-0.00066135,-0.00174785,-0.00203128,0.00188957,0.00888096,0.01393554,0.01247113,0.00477115,-0.00359017,-0.00703863,-0.00401533,0.00089754,0.00462944,0.00410980,0.00297607,0.00127546,0.00099202,0.00004724,-0.00103926,-0.00075583,0.00075583,0.00354294,0.00585765,0.00566870,0.00618833,0.00538526,0.00647176,0.00524354,0.00198404,-0.00368465,-0.00826685,-0.01001470,-0.00807789,-0.00458220,-0.00217300,-0.00085030,-0.00127546,-0.00264539,-0.00538526,-0.00892820,-0.01072328,-0.01001470,-0.00458220,-0.00009448,0.00325950,0.00240920,0.00023620,-0.00108650,-0.00259815,-0.00377913,-0.00684967,-0.00798341,-0.00765274,-0.00330674,-0.00070859,0.00174785,0.00222024,0.00557422,0.01232941,0.02002939,0.02480055,0.02423368,0.02021835,0.01478585,0.01025089,0.00595213,0.00212576,0.00141717,0.00330674,0.00684967,0.00779446,0.00392085,-0.00288159,-0.00708587,-0.00765274,-0.00387361,-0.00212576,-0.00250367,-0.00401533,-0.00311778,0.00184233,0.00836133,0.01067604,0.00812513,0.00051963,-0.00703863,-0.01086500,-0.01091224,-0.00793617,-0.00387361,0.00023620,0.00481839,0.00855028,0.00992022,0.00836133,0.00410980,0.00160613,0.00203128,0.00519630,0.00722759,0.00477115,-0.00051963,-0.00585765,-0.00684967,-0.00444048,-0.00240920,-0.00099202,-0.00118098,0.00075583,0.00500735,0.00784170,0.00831409,0.00599937,0.00510183,0.00689691,0.00902267,0.00718035,0.00165337,-0.00500735,-0.00472391,0.00118098,0.00935335,0.01398278,0.01199874,0.00821961,0.00581041,0.00647176,0.00817237,0.00935335,0.01020365,0.01129015,0.01199874,0.00958954,0.00472391,-0.00103926,-0.00170061,0.00151165,0.00769998,0.01081776,0.01034537,0.00878648,0.00855028,0.00963678,0.00916439,0.00585765,0.00141717,0.00075583,0.00321226,0.00784170,0.00973126,0.00765274,0.00401533,0.00085030,0.00075583,0.00170061,0.00382637,0.00614109,0.00916439,0.01270733,0.01313248,0.01275457,0.00911715,0.00722759,0.00609385,0.00491287,0.00255091,-0.00132270,-0.00519630,-0.00552698,-0.00481839,-0.00259815,-0.00321226,-0.00359017,-0.00160613,0.00472391,0.01360487,0.01870670,0.01842326,0.01162083,0.00510183,0.00056687,0.00028343,0.00089754,0.00273987,0.00448772,0.00845581,0.01124291,0.01166807,0.00755826,0.00089754,-0.00373189,-0.00439324,-0.00222024,0.00094478,0.00207852,0.00363741,0.00524354,0.00784170,0.00736931,0.00505459,0.00118098,-0.00009448,0.00321226,0.00751102,0.01043985,0.00963678,0.00684967,0.00656624,0.00845581,0.01209322,0.01374659,0.01313248,0.01242389,0.01289628,0.01473861,0.01530548,0.01488033,0.01327420,0.01341591,0.01157359,0.00873924,0.00198404,-0.00222024,-0.00118098,0.00543250,0.01313248,0.01403002,0.01029813,0.00444048,0.00382637,0.00647176,0.00836133,0.00642452,0.00108650,-0.00108650,-0.00033067,0.00160613,0.00056687,-0.00325950,-0.00524354,-0.00179509,0.00467667,0.01143187,0.01346315,0.01426622,0.01582511,0.01856498,0.01908461,0.01379383,0.00387361,-0.00458220,-0.00869200,-0.00623557,-0.00203128,0.00042515,0.00245644,0.00259815,0.00538526,0.00675520,0.00784170,0.00666072,0.00656624,0.00746378,0.00968402,0.00821961,0.00533802,-0.00056687,-0.00174785,0.00075583,0.00514907,0.00944783,0.01138463,0.01634474,0.02371405,0.02933550,0.02385576,0.00618833,-0.01832878,-0.03231157,-0.03089439,-0.01341591,0.00462944,0.01738400,0.02069074,0.02239135,0.02097418,0.01856498,0.01039261,0.00217300,-0.00056687,0.00387361,0.01157359,0.01374659,0.00992022,0.00273987,0.00160613,0.00453496,0.00973126,0.01039261,0.00666072,0.00269263,0.00009448,-0.00080307,-0.00259815,-0.00462944,-0.00396809,0.00108650,0.00906991,0.01521100,0.01483309,0.01015641,0.00231472,-0.00292883,-0.00496011,-0.00628280,-0.00377913,-0.00278711,0.00184233,0.00330674,0.00344846,-0.00028343,-0.00292883,-0.00193680,0.00415704,0.01091224,0.01483309,0.01351039,0.01006194,0.00788894,0.00727483,0.00656624,0.00297607,-0.00245644,-0.00656624,-0.00727483,-0.00467667,-0.00222024,-0.00103926,-0.00099202,-0.00080307,0.00099202,0.00155889,0.00103926,-0.00028343,-0.00089754,0.00085030,0.00330674,0.00538526,0.00637728,0.00661348,0.00718035,0.00727483,0.00699139,0.00585765,0.00396809,0.00392085,0.00368465,0.00562146,0.00656624,0.00784170,0.00859752,0.01006194,0.01232941,0.01369935,0.01393554,0.01133739,0.00666072,0.00231472,-0.00113374,-0.00108650,0.00118098,0.00500735,0.00897544,0.01110120,0.01138463,0.00873924,0.00623557,0.00458220,0.00505459,0.00684967,0.00769998,0.00803065,0.00760550,0.00888096,0.01086500,0.01180978,0.01214046,0.00925887,0.00751102,0.00514907,0.00359017,0.00141717,-0.00042515,-0.00113374,-0.00028343,0.00136993,0.00302330,0.00269263,0.00377913,0.00396809,0.00486563,0.00415704,0.00212576,-0.00094478,-0.00363741,-0.00642452,-0.00992022,-0.01266009,-0.01525824,-0.01421898,-0.01086500,-0.00595213,-0.00014172,0.00429876,0.00888096,0.01223494,0.01403002,0.01417174,0.01185702,0.00902267,0.00467667,0.00113374,-0.00188957,-0.00033067,0.00349570,0.01114844,0.01620302,0.01936805,0.01832878,0.01648646,0.01360487,0.01053433,0.00533802,-0.00047239,-0.00533802,-0.00821961,-0.00977850,-0.01039261,-0.01232941,-0.01133739,-0.00930611,-0.00599937,-0.00288159,-0.00259815,-0.00188957,-0.00174785,-0.00066135,-0.00146441,-0.00307054,-0.00590489,-0.00637728,-0.00651900,-0.00486563,-0.00538526,-0.00434600,-0.00297607,0.00018896,0.00170061,0.00122822,-0.00061411,-0.00085030,0.00193680,0.00500735,0.00562146,0.00335398,0.00099202,0.00188957,0.00718035,0.01299076,0.01766744,0.01880118,0.01880118,0.01776191,0.01700609,0.01549444,0.01459689,0.01317972,0.01256561,0.00973126,0.00670796,0.00486563,0.00689691,0.01332144,0.02017111,0.02352509,0.02102142,0.01577787,0.01204598,0.01020365,0.01048709,0.00732207,0.00151165,-0.00377913,-0.00547974,-0.00184233,0.00396809,0.00623557,0.00396809,-0.00231472,-0.00623557,-0.00623557,-0.00018896,0.00689691,0.01488033,0.01946252,0.02224963,0.02106865,0.01591959,0.00836133,0.00127546,-0.00051963,0.00264539,0.00888096,0.01317972,0.01369935,0.01346315,0.01242389,0.01374659,0.01459689,0.01322696,0.01199874,0.01025089,0.01147911,0.01251837,0.01317972,0.01237665,0.01129015,0.01091224,0.01053433,0.00888096,0.00647176,0.00486563,0.00571594,0.00807789,0.00973126,0.00817237,0.00486563,0.00236196,0.00170061,0.00174785,-0.00023620,-0.00500735,-0.00949507,-0.01129015,-0.00973126,-0.00751102,-0.00718035,-0.00968402,-0.01095948,-0.01114844,-0.00921163,-0.00817237,-0.00921163,-0.01043985,-0.01105396,-0.01010917,-0.00982574,-0.01020365,-0.00944783,-0.00581041,0.00089754,0.00614109,0.00718035,0.00359017,0.00056687,0.00056687,0.00406257,0.00628280,0.00316502,-0.00212576,-0.00812513,-0.00873924,-0.00741654,-0.00439324,-0.00311778,-0.00004724,0.00226748,0.00623557,0.00571594,0.00264539,-0.00193680,-0.00505459,-0.00354294,-0.00170061,0.00023620,-0.00103926,-0.00316502,-0.00481839,-0.00505459,-0.00462944,-0.00344846,-0.00188957,0.00085030,0.00415704,0.00642452,0.00817237,0.00661348,0.00628280,0.00472391,0.00477115,0.00562146,0.00675520,0.00935335,0.01152635,0.01346315,0.01162083,0.00855028,0.00354294,0.00075583,0.00075583,0.00179509,0.00264539,0.00023620,-0.00302330,-0.00670796,-0.00684967,-0.00538526,-0.00184233,0.00094478,0.00236196,0.00340122,0.00226748,0.00099202,-0.00198404,-0.00453496,-0.00604661,-0.00510183,-0.00349570,-0.00141717,-0.00018896,0.00075583,0.00330674,0.00599937,0.00803065,0.00680244,0.00387361,0.00051963,-0.00009448,0.00146441,0.00193680,0.00056687,-0.00373189,-0.00689691,-0.00680244,-0.00543250,-0.00250367,-0.00429876,-0.00576317,-0.00855028,-0.00836133,-0.00741654,-0.00647176,-0.00637728,-0.00543250,-0.00292883,0.00042515,0.00264539,0.00113374,-0.00212576,-0.00637728,-0.00878648,-0.01006194,-0.01133739,-0.01242389,-0.01322696,-0.01190426,-0.00845581,-0.00392085,0.00085030,0.00354294,0.00467667,0.00377913,0.00188957,-0.00070859,-0.00160613,-0.00226748,0.00023620,0.00325950,0.00633004,0.00925887,0.01105396,0.01303800,0.01563615,0.01653370,0.01563615,0.01176254,0.00694415,0.00458220,0.00543250,0.00840857,0.01010917,0.00864476,0.00529078,0.00335398,0.00368465,0.00656624,0.00793617,0.00774722,0.00392085,0.00037791,-0.00576317,-0.00902267,-0.01199874,-0.00845581,-0.00198404,0.00722759,0.01138463,0.01147911,0.00684967,0.00396809,0.00283435,0.00344846,0.00222024,-0.00037791,-0.00184233,0.00018896,0.00392085,0.00651900,0.00571594,0.00344846,0.00392085,0.00609385,0.00779446,0.00477115,-0.00184233,-0.00793617,-0.00803065,-0.00410980,0.00245644,0.00547974,0.00543250,0.00359017,0.00193680,0.00146441,0.00122822,0.00259815,0.00311778,0.00429876,0.00188957,-0.00259815,-0.00751102,-0.01034537,-0.00826685,-0.00467667,-0.00094478,0.00051963,0.00094478,0.00075583,0.00028343,-0.00160613,-0.00462944,-0.00576317,-0.00467667,-0.00033067,0.00236196,0.00330674,0.00226748,0.00311778,0.00656624,0.01081776,0.01247113,0.00878648,0.00429876,-0.00080307,-0.00122822,-0.00018896,0.00226748,0.00472391,0.00566870,0.00694415,0.00637728,0.00628280,0.00562146,0.00566870,0.00496011,0.00316502,-0.00042515,-0.00377913,-0.00467667,-0.00335398,-0.00051963,0.00094478,0.00033067,-0.00089754,-0.00273987,-0.00297607,-0.00406257,-0.00448772,-0.00524354,-0.00486563,-0.00311778,-0.00236196,-0.00132270,-0.00321226,-0.00434600,-0.00590489,-0.00557422,-0.00481839,-0.00292883,-0.00344846,-0.00401533,-0.00694415,-0.00779446,-0.00864476,-0.00666072,-0.00628280,-0.00505459,-0.00595213,-0.00590489,-0.00642452,-0.00689691,-0.00817237,-0.00911715,-0.00902267,-0.00656624,-0.00444048,-0.00273987,-0.00160613,-0.00009448,0.00425152,0.00807789,0.01029813,0.00878648,0.00500735,0.00373189,0.00325950,0.00543250,0.00420428,0.00255091,-0.00014172,-0.00108650,-0.00113374,-0.00174785,-0.00023620,0.00236196,0.00968402,0.01454965,0.01596683,0.00897544,0.00018896,-0.00684967,-0.00708587,-0.00344846,0.00179509,0.00425152,0.00656624,0.00784170,0.00996746,0.00977850,0.00878648,0.00514907,0.00259815,-0.00085030,-0.00425152,-0.00869200,-0.01176254,-0.01284904,-0.01067604,-0.00741654,-0.00453496,-0.00278711,-0.00170061,-0.00165337,-0.00226748,-0.00392085,-0.00637728,-0.00741654,-0.00736931,-0.00609385,-0.00481839,-0.00477115,-0.00566870,-0.00703863,-0.00765274,-0.00694415,-0.00595213,-0.00481839,-0.00496011,-0.00651900,-0.00760550,-0.00902267,-0.00864476,-0.00812513,-0.00736931,-0.00680244,-0.00647176,-0.00547974,-0.00699139,-0.00949507,-0.01511652,-0.01941528,-0.02102142,-0.01795087,-0.01294352,-0.00703863,-0.00340122,-0.00245644,-0.00340122,-0.00699139,-0.01062881,-0.01284904,-0.01317972,-0.01001470,-0.00656624,-0.00439324,-0.00321226,-0.00406257,-0.00311778,-0.00259815,-0.00203128,-0.00255091,-0.00496011,-0.00689691,-0.00940059,-0.01124291,-0.01232941,-0.01152635,-0.00760550,-0.00231472,0.00236196,0.00288159,0.00051963,-0.00359017,-0.00543250,-0.00566870,-0.00401533,-0.00401533,-0.00396809,-0.00439324,-0.00330674,-0.00217300,-0.00141717,-0.00160613,-0.00193680,0.00004724,0.00207852,0.00429876,0.00406257,0.00127546,-0.00004724,-0.00094478,0.00099202,0.00179509,-0.00023620,-0.00321226,-0.00784170,-0.00836133,-0.00751102,-0.00330674,0.00070859,0.00604661,0.01081776,0.01591959,0.01719505,0.01535272,0.00840857,0.00004724,-0.00831409,-0.01332144,-0.01464413,-0.01218770,-0.00751102,-0.00155889,0.00236196,0.00581041,0.00543250,0.00562146,0.00302330,0.00085030,-0.00264539,-0.00557422,-0.00736931,-0.00736931,-0.00618833,-0.00406257,-0.00278711,-0.00080307,-0.00066135,-0.00056687,-0.00311778,-0.00732207,-0.01247113,-0.01539996,-0.01629750,-0.01374659,-0.01010917,-0.00666072,-0.00377913,-0.00155889,-0.00099202,-0.00023620,-0.00103926,-0.00193680,-0.00325950,-0.00500735,-0.00609385,-0.00769998,-0.00784170,-0.00878648,-0.00741654,-0.00585765,-0.00292883,-0.00070859,-0.00094478,-0.00316502,-0.00571594,-0.00746378,-0.00576317,-0.00420428,-0.00288159,-0.00297607,-0.00354294,-0.00288159,-0.00075583,0.00151165,0.00330674,0.00406257,0.00392085,0.00236196,0.00014172,-0.00354294,-0.00401533,-0.00396809,-0.00108650,-0.00075583,-0.00103926,-0.00292883,-0.00226748,-0.00118098,0.00018896,-0.00217300,-0.00590489,-0.01029813,-0.01152635,-0.01086500,-0.00963678,-0.00864476,-0.00826685,-0.00741654,-0.00595213,-0.00590489,-0.00486563,-0.00491287,-0.00165337,0.00141717,0.00505459,0.00609385,0.00571594,0.00377913,0.00103926,-0.00155889,-0.00519630,-0.00656624,-0.00675520,-0.00368465,0.00000000,0.00396809,0.00486563,0.00420428,0.00042515,-0.00415704,-0.00793617,-0.01147911,-0.01171531,-0.01162083,-0.00954231,-0.00741654,-0.00576317,-0.00429876,-0.00467667,-0.00458220,-0.00519630,-0.00420428,-0.00269263,-0.00193680,-0.00113374,-0.00179509,-0.00160613,-0.00118098,-0.00056687,-0.00042515,-0.00051963,-0.00122822,-0.00061411,-0.00113374,-0.00118098,-0.00170061,-0.00174785,0.00070859,0.00170061,0.00269263,-0.00004724,-0.00349570,-0.00727483,-0.00949507,-0.01105396,-0.01266009,-0.01308524,-0.01275457,-0.00902267,-0.00481839,-0.00118098,-0.00028343,-0.00085030,-0.00245644,-0.00236196,-0.00259815,-0.00321226,-0.00462944,-0.00666072,-0.00812513,-0.00869200,-0.00897544,-0.00769998,-0.00510183,-0.00075583,0.00311778,0.00377913,0.00113374,-0.00410980,-0.00736931,-0.00793617,-0.00453496,-0.00179509,0.00075583,0.00018896,0.00042515,0.00028343,0.00136993,0.00255091,0.00335398,0.00462944,0.00458220,0.00363741,0.00018896,-0.00439324,-0.00897544,-0.01180978,-0.01303800,-0.01242389,-0.01171531,-0.01091224,-0.00949507,-0.00949507,-0.00826685,-0.00935335,-0.00911715,-0.00892820,-0.00666072,-0.00255091,0.00094478,0.00448772,0.00453496,0.00448772,0.00325950,0.00349570,0.00344846,0.00321226,0.00170061,-0.00004724,-0.00070859,-0.00141717,-0.00141717,-0.00349570,-0.00637728,-0.00817237,-0.00911715,-0.00661348,-0.00439324,-0.00217300,-0.00193680,-0.00245644,-0.00264539,-0.00245644,-0.00203128,-0.00316502,-0.00500735,-0.00694415,-0.00803065,-0.00855028,-0.00869200,-0.00987298,-0.01081776,-0.00982574,-0.00859752,-0.00543250,-0.00410980,-0.00392085,-0.00392085,-0.00321226,-0.00179509,-0.00179509,-0.00382637,-0.00751102,-0.00925887,-0.00906991,-0.00703863,-0.00566870,-0.00670796,-0.00590489,-0.00637728,-0.00458220,-0.00666072,-0.00973126,-0.01223494,-0.00987298,-0.00226748,0.00529078,0.00968402,0.00821961,0.00595213,0.00429876,0.00510183,0.00477115,0.00179509,-0.00259815,-0.00703863,-0.01081776,-0.01256561,-0.01412450,-0.01162083,-0.00755826,-0.00198404,0.00018896,-0.00118098,-0.00467667,-0.00694415,-0.00746378,-0.00751102,-0.00845581,-0.00973126,-0.00784170,-0.00359017,0.00193680,0.00387361,0.00255091,0.00009448,-0.00226748,-0.00198404,-0.00377913,-0.00439324,-0.00571594,-0.00316502,-0.00009448,0.00278711,0.00066135,-0.00425152,-0.01072328,-0.01412450,-0.01582511,-0.01506928,-0.01469137,-0.01440794,-0.01317972,-0.01232941,-0.01006194,-0.00916439,-0.00878648,-0.00977850,-0.01020365,-0.01067604,-0.00968402,-0.00873924,-0.00840857,-0.00888096,-0.00968402,-0.01091224,-0.01081776,-0.01006194,-0.00873924,-0.00718035,-0.00562146,-0.00496011,-0.00439324,-0.00439324,-0.00363741,-0.00259815,-0.00066135,-0.00136993,-0.00170061,-0.00448772,-0.00524354,-0.00529078,-0.00401533,-0.00264539,-0.00188957,-0.00033067,0.00193680,0.00599937,0.00864476,0.01039261,0.00906991,0.00666072,0.00354294,-0.00014172,-0.00344846,-0.00609385,-0.00661348,-0.00425152,-0.00184233,0.00099202,0.00023620,-0.00014172,-0.00070859,-0.00033067,0.00037791,-0.00226748,-0.00514907,-0.00817237,-0.00769998,-0.00420428,-0.00184233,-0.00127546,-0.00330674,-0.00486563,-0.00401533,-0.00127546,0.00127546,0.00250367,0.00250367,0.00212576,0.00198404,0.00174785,0.00033067,-0.00023620,-0.00099202,0.00018896,0.00108650,0.00136993,0.00141717,0.00165337,0.00217300,0.00359017,0.00373189,0.00420428,0.00359017,0.00330674,0.00207852,0.00028343,-0.00075583,-0.00146441,-0.00009448,0.00061411,0.00056687,0.00037791,0.00004724,0.00236196,0.00458220,0.00599937,0.00344846,-0.00066135,-0.00651900,-0.00807789,-0.00812513,-0.00420428,-0.00155889,0.00094478,0.00174785,0.00236196,0.00330674,0.00415704,0.00377913,0.00335398,0.00184233,0.00165337,0.00141717,0.00066135,-0.00132270,-0.00462944,-0.00585765,-0.00628280,-0.00396809,-0.00259815,-0.00212576,-0.00165337,-0.00132270,0.00066135,0.00127546,0.00056687,-0.00160613,-0.00330674,-0.00283435,-0.00151165,0.00000000,-0.00094478,-0.00108650,-0.00136993,0.00094478,0.00212576,0.00188957,-0.00099202,-0.00330674,-0.00410980,-0.00250367,-0.00080307,-0.00066135,-0.00174785,-0.00321226,-0.00387361,-0.00359017,-0.00420428,-0.00486563,-0.00661348,-0.00713311,-0.00703863,-0.00623557,-0.00547974,-0.00406257,-0.00217300,0.00066135,0.00321226,0.00283435,0.00094478,-0.00406257,-0.00765274,-0.01095948,-0.01091224,-0.00982574,-0.00576317,-0.00198404,0.00184233,0.00302330,0.00118098,-0.00188957,-0.00614109,-0.00751102,-0.00859752,-0.00760550,-0.00751102,-0.00680244,-0.00694415,-0.00595213,-0.00623557,-0.00628280,-0.00788894,-0.00949507,-0.01133739,-0.01147911,-0.01072328,-0.00840857,-0.00623557,-0.00481839,-0.00491287,-0.00628280,-0.00788894,-0.00883372,-0.00760550,-0.00434600,-0.00033067,0.00240920,0.00269263,0.00056687,-0.00250367,-0.00519630,-0.00656624,-0.00788894,-0.00746378,-0.00769998,-0.00543250,-0.00354294,-0.00136993,-0.00070859,-0.00188957,-0.00307054,-0.00519630,-0.00651900,-0.00826685,-0.00949507,-0.00902267,-0.00699139,-0.00297607,-0.00085030,0.00000000,-0.00231472,-0.00505459,-0.00675520,-0.00812513,-0.00722759,-0.00656624,-0.00401533,-0.00160613,0.00089754,0.00184233,0.00089754,-0.00018896,-0.00160613,-0.00259815,-0.00444048,-0.00694415,-0.00930611,-0.00906991,-0.00562146,-0.00193680,0.00255091,0.00307054,0.00349570,0.00387361,0.00472391,0.00552698,0.00410980,0.00056687,-0.00108650,-0.00217300,0.00080307,0.00160613,0.00193680,-0.00056687,-0.00207852,-0.00203128,-0.00170061,-0.00108650,-0.00349570,-0.00491287,-0.00439324,-0.00269263,0.00061411,0.00018896,-0.00165337,-0.00382637,-0.00529078,-0.00425152,-0.00410980,-0.00401533,-0.00533802,-0.00458220,-0.00377913,-0.00047239,0.00207852,0.00467667,0.00637728,0.00647176,0.00420428,0.00066135,-0.00415704,-0.00510183,-0.00429876,0.00000000,0.00278711,0.00429876,0.00340122,0.00240920,0.00165337,0.00099202,-0.00023620,-0.00255091,-0.00486563,-0.00576317,-0.00510183,-0.00410980,-0.00396809,-0.00491287,-0.00547974,-0.00425152,-0.00146441,0.00188957,0.00335398,0.00415704,0.00292883,0.00335398,0.00311778,0.00406257,0.00406257,0.00472391,0.00519630,0.00609385,0.00633004,0.00481839,0.00278711,0.00004724,-0.00056687,-0.00080307,0.00141717,0.00207852,0.00344846,0.00179509,0.00009448,-0.00264539,-0.00382637,-0.00321226,-0.00075583,0.00146441,0.00359017,0.00406257,0.00434600,0.00529078,0.00670796,0.00774722,0.00779446,0.00552698,0.00193680,-0.00179509,-0.00637728,-0.00935335,-0.01176254,-0.01171531,-0.01020365,-0.00699139,-0.00453496,-0.00231472,-0.00070859,0.00151165,0.00496011,0.00963678,0.01351039,0.01639198,0.01606131,0.01436070,0.01048709,0.00656624,0.00340122,0.00066135,0.00037791,-0.00047239,-0.00070859,-0.00226748,-0.00415704,-0.00519630,-0.00500735,-0.00311778,-0.00179509,-0.00047239,-0.00155889,-0.00259815,-0.00396809,-0.00401533,-0.00410980,-0.00415704,-0.00415704,-0.00434600,-0.00359017,-0.00207852,-0.00203128,-0.00188957,-0.00387361,-0.00576317,-0.00590489,-0.00623557,-0.00420428,-0.00297607,-0.00042515,0.00222024,0.00510183,0.00637728,0.00566870,0.00363741,0.00184233,0.00160613,0.00335398,0.00496011,0.00628280,0.00651900,0.00732207,0.00727483,0.00751102,0.00491287,0.00354294,0.00151165,0.00288159,0.00325950,0.00396809,0.00198404,0.00094478,0.00070859,0.00217300,0.00396809,0.00420428,0.00491287,0.00510183,0.00675520,0.00675520,0.00500735,0.00113374,-0.00198404,-0.00288159,-0.00056687,0.00420428,0.00906991,0.01431346,0.01658094,0.01530548,0.00869200,-0.00193680,-0.01129015,-0.01686437,-0.01478585,-0.00892820,-0.00075583,0.00604661,0.01025089,0.01299076,0.01322696,0.01180978,0.00826685,0.00396809,0.00018896,-0.00155889,-0.00231472,-0.00151165,-0.00160613,-0.00136993,-0.00051963,0.00075583,0.00255091,0.00359017,0.00264539,0.00165337,-0.00014172,-0.00051963,-0.00146441,-0.00240920,-0.00439324,-0.00590489,-0.00628280,-0.00647176,-0.00637728,-0.00793617,-0.00963678,-0.01020365,-0.01067604,-0.00888096,-0.01001470,-0.00968402,-0.01091224,-0.00996746,-0.00850304,-0.00623557,-0.00481839,-0.00377913,-0.00292883,-0.00269263,-0.00203128,-0.00250367,-0.00250367,-0.00387361,-0.00472391,-0.00628280,-0.00680244,-0.00666072,-0.00382637,-0.00170061,0.00188957,0.00321226,0.00359017,0.00410980,0.00325950,0.00354294,0.00273987,0.00278711,0.00302330,0.00396809,0.00590489,0.00741654,0.00859752,0.00855028,0.00727483,0.00609385,0.00448772,0.00292883,0.00122822,-0.00023620,-0.00113374,-0.00028343,0.00056687,0.00132270,0.00151165,0.00122822,0.00203128,0.00307054,0.00401533,0.00406257,0.00264539,0.00198404,0.00179509,0.00255091,0.00259815,0.00146441,-0.00042515,-0.00141717,-0.00188957,-0.00085030,-0.00089754,-0.00136993,-0.00146441,-0.00127546,0.00042515,0.00217300,0.00292883,0.00311778,0.00198404,0.00094478,-0.00103926,-0.00207852,-0.00330674,-0.00240920,-0.00014172,0.00179509,0.00401533,0.00340122,0.00368465,0.00377913,0.00538526,0.00590489,0.00576317,0.00302330,0.00047239,-0.00047239,0.00037791,0.00255091,0.00382637,0.00363741,0.00283435,0.00236196,0.00269263,0.00392085,0.00595213,0.00840857,0.01119567,0.01379383,0.01308524,0.01129015,0.00713311,0.00448772,0.00259815,0.00141717,-0.00037791,-0.00273987,-0.00307054,-0.00136993,0.00269263,0.00585765,0.00746378,0.00666072,0.00618833,0.00581041,0.00784170,0.00746378,0.00760550,0.00519630,0.00415704,0.00387361,0.00458220,0.00533802,0.00524354,0.00481839,0.00453496,0.00533802,0.00651900,0.00831409,0.00987298,0.01157359,0.01266009,0.01223494,0.00992022,0.00609385,0.00325950,0.00203128,0.00448772,0.00699139,0.01001470,0.01091224,0.01091224,0.01043985,0.00892820,0.00618833,0.00363741,0.00056687,0.00037791,0.00023620,0.00037791,0.00056687,-0.00028343,0.00160613,0.00269263,0.00547974,0.00647176,0.00812513,0.00949507,0.01029813,0.00958954,0.00651900,0.00410980,0.00259815,0.00373189,0.00425152,0.00377913,0.00231472,0.00193680,0.00321226,0.00472391,0.00462944,0.00321226,0.00207852,0.00458220,0.00812513,0.01152635,0.01185702,0.00930611,0.00769998,0.00633004,0.00765274,0.00888096,0.01081776,0.01332144,0.01497481,0.01558891,0.01336868,0.00977850,0.00566870,0.00307054,0.00165337,0.00042515,-0.00018896,-0.00108650,-0.00009448,0.00165337,0.00467667,0.00722759,0.00940059,0.00968402,0.00925887,0.00793617,0.00661348,0.00599937,0.00496011,0.00396809,0.00255091,0.00103926,0.00037791,-0.00061411,-0.00037791,-0.00146441,-0.00066135,-0.00028343,0.00170061,0.00170061,0.00165337,0.00037791,0.00061411,0.00151165,0.00292883,0.00231472,0.00141717,0.00051963,0.00099202,0.00316502,0.00467667,0.00486563,0.00415704,0.00222024,0.00170061,0.00014172,-0.00009448,-0.00146441,-0.00108650,0.00018896,0.00264539,0.00377913,0.00307054,-0.00051963,-0.00462944,-0.00661348,-0.00533802,-0.00061411,0.00547974,0.00916439,0.01034537,0.00821961,0.00505459,0.00222024,0.00056687,0.00075583,0.00240920,0.00462944,0.00661348,0.00614109,0.00415704,0.00094478,-0.00113374,-0.00099202,0.00009448,0.00141717,0.00085030,0.00085030,-0.00028343,0.00160613,0.00297607,0.00519630,0.00628280,0.00519630,0.00420428,0.00222024,0.00245644,0.00359017,0.00566870,0.00666072,0.00547974,0.00311778,0.00127546,0.00170061,0.00477115,0.00817237,0.01001470,0.00916439,0.00581041,0.00136993,-0.00335398,-0.00670796,-0.00831409,-0.00769998,-0.00439324,-0.00085030,0.00330674,0.00628280,0.00973126,0.01294352,0.01606131,0.01724228,0.01558891,0.01204598,0.00831409,0.00533802,0.00429876,0.00316502,0.00259815,0.00174785,0.00160613,0.00179509,0.00136993,0.00061411,-0.00056687,-0.00089754,-0.00051963,-0.00028343,-0.00042515,-0.00203128,-0.00325950,-0.00330674,-0.00269263,-0.00080307,-0.00094478,-0.00028343,-0.00070859,0.00212576,0.00524354,0.00949507,0.01110120,0.01124291,0.00935335,0.00831409,0.00755826,0.00642452,0.00439324,0.00113374,-0.00103926,-0.00188957,-0.00136993,-0.00061411,-0.00170061,-0.00240920,-0.00425152,-0.00283435,-0.00222024,0.00042515,0.00136993,0.00325950,0.00496011,0.00614109,0.00618833,0.00481839,0.00359017,0.00302330,0.00377913,0.00481839,0.00486563,0.00462944,0.00472391,0.00533802,0.00703863,0.00703863,0.00585765,0.00363741,0.00184233,0.00184233,0.00236196,0.00340122,0.00273987,0.00132270,-0.00108650,-0.00264539,-0.00302330,-0.00127546,0.00118098,0.00410980,0.00406257,0.00217300,-0.00344846,-0.00845581,-0.01176254,-0.01081776,-0.00604661,0.00051963,0.00623557,0.00873924,0.00736931,0.00330674,-0.00179509,-0.00481839,-0.00590489,-0.00410980,-0.00094478,0.00070859,0.00203128,0.00009448,-0.00122822,-0.00321226,-0.00292883,-0.00245644,-0.00070859,0.00023620,0.00113374,0.00056687,-0.00014172,-0.00269263,-0.00425152,-0.00666072,-0.00779446,-0.00930611,-0.01010917,-0.01143187,-0.01072328,-0.01081776,-0.00869200,-0.00807789,-0.00684967,-0.00623557,-0.00467667,-0.00325950,-0.00160613,-0.00184233,-0.00255091,-0.00373189,-0.00467667,-0.00425152,-0.00415704,-0.00354294,-0.00311778,-0.00344846,-0.00278711,-0.00273987,-0.00170061,0.00018896,0.00160613,0.00354294,0.00392085,0.00321226,0.00122822,-0.00009448,-0.00132270,0.00047239,0.00203128,0.00477115,0.00661348,0.00727483,0.00793617,0.00656624,0.00505459,0.00222024,-0.00094478,-0.00359017,-0.00491287,-0.00604661,-0.00604661,-0.00614109,-0.00505459,-0.00307054,-0.00056687,0.00085030,0.00051963,-0.00170061,-0.00377913,-0.00529078,-0.00543250,-0.00519630,-0.00571594,-0.00477115,-0.00496011,-0.00278711,-0.00288159,-0.00307054,-0.00396809,-0.00439324,-0.00297607,-0.00113374,-0.00014172,-0.00009448,-0.00047239,-0.00075583,0.00113374,0.00089754,0.00273987,0.00179509,0.00325950,0.00533802,0.00769998,0.00949507,0.00897544,0.00647176,0.00392085,0.00250367,0.00302330,0.00538526,0.00769998,0.00869200,0.00798341,0.00500735,0.00155889,-0.00056687,-0.00108650,0.00037791,0.00217300,0.00340122,0.00354294,0.00500735,0.00623557,0.00935335,0.01067604,0.01025089,0.00736931,0.00519630,0.00344846,0.00500735,0.00562146,0.00533802,0.00434600,0.00188957,0.00217300,0.00184233,0.00264539,0.00288159,0.00302330,0.00410980,0.00581041,0.00595213,0.00547974,0.00278711,0.00118098,0.00075583,0.00188957,0.00387361,0.00481839,0.00618833,0.00628280,0.00689691,0.00595213,0.00514907,0.00316502,0.00349570,0.00363741,0.00670796,0.00807789,0.00977850,0.00949507,0.00845581,0.00680244,0.00510183,0.00344846,0.00245644,0.00259815,0.00382637,0.00581041,0.00840857,0.00977850,0.01256561,0.01492757,0.01785639,0.01927357,0.01842326,0.01511652,0.01157359,0.00812513,0.00486563,0.00269263,-0.00108650,-0.00207852,-0.00193680,0.00146441,0.00533802,0.00812513,0.00864476,0.00817237,0.00746378,0.00788894,0.00807789,0.00722759,0.00562146,0.00325950,0.00207852,0.00222024,0.00278711,0.00448772,0.00604661,0.00670796,0.00793617,0.00774722,0.00826685,0.00784170,0.00807789,0.00680244,0.00661348,0.00656624,0.00821961,0.01001470,0.01058157,0.00921163,0.00590489,0.00444048,0.00349570,0.00514907,0.00633004,0.00727483,0.00755826,0.00817237,0.00821961,0.00769998,0.00538526,0.00212576,-0.00160613,-0.00330674,-0.00429876,-0.00392085,-0.00349570,-0.00321226,-0.00240920,-0.00099202,-0.00037791,0.00051963,-0.00151165,-0.00311778,-0.00562146,-0.00599937,-0.00524354,-0.00349570,-0.00222024,-0.00184233,-0.00151165,-0.00141717,-0.00099202,-0.00080307,-0.00151165,-0.00193680,-0.00236196,-0.00217300,-0.00118098,-0.00094478,-0.00056687,-0.00047239,-0.00085030,-0.00103926,-0.00255091,-0.00406257,-0.00557422,-0.00647176,-0.00623557,-0.00666072,-0.00666072,-0.00788894,-0.00760550,-0.00746378,-0.00562146,-0.00519630,-0.00434600,-0.00491287,-0.00410980,-0.00363741,-0.00259815,-0.00292883,-0.00453496,-0.00599937,-0.00755826,-0.00713311,-0.00680244,-0.00670796,-0.00788894,-0.00982574,-0.01015641,-0.00992022,-0.00826685,-0.00708587,-0.00623557,-0.00496011,-0.00335398,-0.00155889,-0.00113374,-0.00240920,-0.00453496,-0.00751102,-0.00869200,-0.00992022,-0.01020365,-0.00954231,-0.00836133,-0.00514907,-0.00255091,0.00028343,0.00113374,0.00118098,0.00066135,-0.00056687,-0.00132270,-0.00330674,-0.00486563,-0.00637728,-0.00741654,-0.00774722,-0.00779446,-0.00732207,-0.00680244,-0.00335398,0.00070859,0.00859752,0.01469137,0.01828155,0.01625026,0.00935335,0.00094478,-0.00566870,-0.00869200,-0.00788894,-0.00618833,-0.00486563,-0.00486563,-0.00448772,-0.00467667,-0.00307054,-0.00250367,-0.00222024,-0.00292883,-0.00377913,-0.00491287,-0.00415704,-0.00420428,-0.00316502,-0.00288159,-0.00207852,-0.00070859,0.00193680,0.00311778,0.00330674,0.00075583,-0.00170061,-0.00292883,-0.00297607,-0.00222024,-0.00302330,-0.00368465,-0.00510183,-0.00415704,-0.00316502,-0.00113374,-0.00004724,0.00141717,0.00240920,0.00392085,0.00387361,0.00273987,0.00226748,0.00170061,0.00292883,0.00321226,0.00250367,0.00009448,-0.00132270,-0.00278711,-0.00193680,-0.00155889,0.00000000,0.00103926,0.00335398,0.00462944,0.00538526,0.00307054,0.00056687,-0.00302330,-0.00392085,-0.00377913,-0.00212576,0.00056687,0.00354294,0.00628280,0.00817237,0.00732207,0.00486563,0.00212576,0.00070859,0.00080307,0.00236196,0.00226748,0.00222024,0.00136993,0.00207852,0.00311778,0.00538526,0.00538526,0.00566870,0.00467667,0.00359017,0.00335398,0.00113374,0.00127546,0.00056687,0.00307054,0.00458220,0.00609385,0.00477115,0.00311778,0.00042515,-0.00070859,-0.00188957,-0.00160613,-0.00160613,0.00151165,0.00453496,0.00826685,0.00996746,0.00888096,0.00642452,0.00529078,0.00505459,0.00708587,0.00817237,0.00788894,0.00684967,0.00519630,0.00401533,0.00349570,0.00259815,0.00288159,0.00236196,0.00330674,0.00344846,0.00340122,0.00316502,0.00170061,0.00165337,0.00103926,0.00136993,0.00047239,-0.00099202,-0.00226748,-0.00297607,-0.00174785,-0.00009448,0.00155889,0.00288159,0.00278711,0.00340122,0.00292883,0.00325950,0.00255091,0.00255091,0.00155889,0.00141717,0.00037791,-0.00023620,0.00004724,0.00033067,0.00184233,0.00245644,0.00212576,0.00184233,0.00127546,0.00188957,0.00250367,0.00278711,0.00236196,0.00250367,0.00264539,0.00368465,0.00316502,0.00250367,0.00014172,-0.00023620,0.00004724,0.00198404,0.00354294,0.00396809,0.00340122,0.00198404,-0.00018896,-0.00198404,-0.00359017,-0.00311778,-0.00165337,0.00136993,0.00325950,0.00377913,0.00198404,-0.00151165,-0.00359017,-0.00543250,-0.00462944,-0.00349570,-0.00188957,-0.00094478,0.00070859,0.00099202,0.00103926,0.00061411,-0.00108650,-0.00203128,-0.00264539,-0.00264539,-0.00217300,-0.00113374,-0.00146441,-0.00042515,-0.00113374,-0.00146441,-0.00269263,-0.00311778,-0.00240920,-0.00108650,0.00042515,-0.00061411,-0.00302330,-0.00661348,-0.01010917,-0.01058157,-0.01015641,-0.00694415,-0.00321226,0.00037791,0.00448772,0.00614109,0.00821961,0.00760550,0.00694415,0.00429876,0.00099202,-0.00255091,-0.00604661,-0.00774722,-0.00892820,-0.00784170,-0.00760550,-0.00557422,-0.00486563,-0.00392085,-0.00415704,-0.00505459,-0.00642452,-0.00765274,-0.00845581,-0.00817237,-0.00666072,-0.00387361,-0.00146441,0.00061411,0.00014172,-0.00037791,-0.00184233,-0.00099202,0.00004724,0.00146441,0.00184233,0.00033067,-0.00113374,-0.00373189,-0.00486563,-0.00481839,-0.00203128,0.00264539,0.00760550,0.00944783,0.00873924,0.00481839,0.00075583,-0.00245644,-0.00557422,-0.00689691,-0.00684967,-0.00212576,0.00410980,0.01147911,0.01412450,0.01280181,0.00793617,0.00448772,0.00174785,0.00146441,-0.00033067,-0.00155889,-0.00288159,-0.00250367,-0.00245644,-0.00292883,-0.00462944,-0.00529078,-0.00590489,-0.00420428,-0.00533802,-0.00533802,-0.00803065,-0.00769998,-0.00751102,-0.00642452,-0.00604661,-0.00684967,-0.00699139,-0.00699139,-0.00576317,-0.00514907,-0.00496011,-0.00467667,-0.00519630,-0.00467667,-0.00477115,-0.00439324,-0.00434600,-0.00453496,-0.00505459,-0.00562146,-0.00566870,-0.00462944,-0.00297607,-0.00136993,-0.00080307,-0.00141717,-0.00297607,-0.00425152,-0.00477115,-0.00491287,-0.00382637,-0.00368465,-0.00377913,-0.00373189,-0.00434600,-0.00259815,-0.00170061,-0.00023620,-0.00014172,-0.00198404,-0.00292883,-0.00524354,-0.00566870,-0.00680244,-0.00741654,-0.00670796,-0.00462944,-0.00132270,0.00146441,0.00188957,0.00122822,-0.00094478,-0.00103926,-0.00165337,-0.00103926,-0.00151165,-0.00113374,-0.00103926,-0.00037791,-0.00070859,-0.00075583,-0.00103926,0.00042515,0.00094478,0.00193680,0.00103926,0.00066135,0.00047239,0.00056687,-0.00089754,-0.00500735,-0.00949507,-0.01242389,-0.01081776,-0.00666072,-0.00236196,-0.00033067,-0.00113374,-0.00151165,-0.00193680,-0.00113374,-0.00089754,-0.00193680,-0.00240920,-0.00344846,-0.00245644,-0.00250367,-0.00217300,-0.00231472,-0.00288159,-0.00273987,-0.00316502,-0.00359017,-0.00387361,-0.00335398,-0.00269263,-0.00118098,-0.00066135,-0.00028343,0.00056687,0.00051963,0.00203128,0.00127546,0.00033067,-0.00075583,-0.00278711,-0.00207852,-0.00307054,-0.00217300,-0.00259815,-0.00245644,-0.00136993,-0.00028343,0.00174785,0.00283435,0.00269263,0.00226748,0.00108650,0.00136993,0.00193680,0.00387361,0.00538526,0.00566870,0.00448772,0.00217300,0.00023620,-0.00099202,-0.00033067,0.00118098,0.00151165,0.00193680,-0.00127546,-0.00278711,-0.00571594,-0.00557422,-0.00547974,-0.00373189,-0.00259815,-0.00108650,-0.00061411,0.00023620,-0.00132270,-0.00250367,-0.00633004,-0.00793617,-0.00892820,-0.00718035,-0.00335398,-0.00037791,0.00325950,0.00340122,0.00420428,0.00236196,0.00207852,0.00113374,0.00113374,0.00217300,0.00203128,0.00226748,0.00151165,0.00108650,0.00184233,0.00226748,0.00222024,0.00136993,-0.00028343,-0.00047239,0.00014172,0.00094478,0.00141717,0.00037791,-0.00047239,-0.00037791,0.00075583,0.00222024,0.00387361,0.00344846,0.00410980,0.00288159,0.00311778,0.00160613,0.00132270,-0.00056687,-0.00127546,-0.00297607,-0.00297607,-0.00288159,-0.00118098,0.00023620,-0.00028343,-0.00075583,-0.00302330,-0.00273987,-0.00155889,0.00061411,0.00198404,0.00188957,0.00056687,0.00033067,0.00070859,0.00217300,0.00311778,0.00255091,0.00151165,0.00009448,-0.00018896,0.00066135,0.00217300,0.00335398,0.00363741,0.00264539,0.00165337,0.00009448,-0.00023620,-0.00155889,-0.00217300,-0.00250367,-0.00165337,0.00085030,0.00297607,0.00382637,0.00340122,0.00203128,0.00118098,0.00122822,0.00085030,0.00118098,0.00099202,0.00132270,0.00198404,0.00080307,0.00033067,-0.00170061,-0.00155889,-0.00136993,-0.00070859,-0.00066135,-0.00094478,-0.00113374,-0.00033067,0.00014172,0.00108650,0.00061411,0.00061411,0.00028343,0.00000000,-0.00014172,-0.00222024,-0.00245644,-0.00363741,-0.00174785,-0.00070859,0.00094478,0.00146441,0.00203128,0.00250367,0.00387361,0.00406257,0.00486563,0.00401533,0.00321226,0.00141717,0.00000000,-0.00141717,-0.00179509,-0.00085030,-0.00033067,0.00080307,-0.00009448,-0.00047239,-0.00174785,-0.00042515,-0.00033067,0.00122822,0.00085030,-0.00033067,-0.00103926,-0.00207852,-0.00113374,-0.00028343,0.00028343,0.00089754,0.00042515,0.00127546,0.00146441,0.00170061,0.00132270,0.00113374,0.00108650,0.00198404,0.00231472,0.00203128,0.00151165,0.00066135,0.00051963,-0.00014172,-0.00094478,-0.00198404,-0.00325950,-0.00245644,-0.00207852,-0.00103926,-0.00042515,-0.00018896,0.00066135,0.00188957,0.00217300,0.00236196,0.00146441,0.00136993,0.00222024,0.00245644,0.00349570,0.00188957,0.00080307,-0.00108650,-0.00231472,-0.00269263,-0.00240920,-0.00179509,-0.00014172,0.00047239,0.00094478,-0.00066135,-0.00179509,-0.00344846,-0.00297607,-0.00269263,-0.00184233,-0.00174785,-0.00222024,-0.00236196,-0.00198404,-0.00160613,-0.00118098,-0.00155889,-0.00184233,-0.00212576,-0.00174785,-0.00141717,-0.00132270,-0.00217300,-0.00325950,-0.00505459,-0.00538526,-0.00595213,-0.00453496,-0.00321226,-0.00174785,-0.00023620,-0.00061411,-0.00033067,-0.00212576,-0.00278711,-0.00382637,-0.00406257,-0.00392085,-0.00429876,-0.00439324,-0.00387361,-0.00387361,-0.00222024,-0.00255091,-0.00155889,-0.00132270,-0.00108650,0.00000000,0.00023620,0.00018896,-0.00028343,-0.00113374,-0.00207852,-0.00217300,-0.00259815,-0.00250367,-0.00198404,-0.00151165,-0.00042515,-0.00023620,-0.00018896,-0.00170061,-0.00240920,-0.00396809,-0.00392085,-0.00410980,-0.00373189,-0.00382637,-0.00349570,-0.00387361,-0.00377913,-0.00377913,-0.00392085,-0.00269263,-0.00250367,-0.00151165,-0.00165337,-0.00212576,-0.00236196,-0.00302330,-0.00283435,-0.00236196,-0.00222024,-0.00108650,-0.00085030,0.00004724,-0.00061411,-0.00099202,-0.00193680,-0.00217300,-0.00136993,-0.00018896,0.00085030,0.00212576,0.00222024,0.00193680,0.00089754,-0.00070859,-0.00236196,-0.00283435,-0.00311778,-0.00245644,-0.00179509,-0.00184233,-0.00108650,-0.00155889,-0.00089754,-0.00188957,-0.00184233,-0.00132270,0.00033067,0.00273987,0.00420428,0.00359017,0.00222024,-0.00056687,-0.00127546,-0.00136993,0.00004724,0.00089754,0.00184233,0.00174785,0.00179509,0.00207852,0.00231472,0.00264539,0.00340122,0.00311778,0.00325950,0.00264539,0.00160613,0.00051963,-0.00070859,-0.00108650,-0.00023620,0.00155889,0.00269263,0.00392085,0.00307054,0.00297607,0.00193680,0.00236196,0.00226748,0.00250367,0.00273987,0.00212576,0.00217300,0.00089754,-0.00023620,-0.00103926,-0.00226748,-0.00207852,-0.00278711,-0.00325950,-0.00415704,-0.00387361,-0.00311778,-0.00113374,0.00014172,0.00099202,0.00004724,-0.00066135,-0.00203128,-0.00288159,-0.00245644,-0.00231472,-0.00056687,0.00047239,0.00075583,0.00066135,-0.00108650,-0.00184233,-0.00217300,-0.00184233,-0.00103926,-0.00066135,-0.00061411,0.00014172,0.00056687,0.00136993,0.00118098,0.00085030,-0.00051963,-0.00108650,-0.00240920,-0.00236196,-0.00297607,-0.00255091,-0.00231472,-0.00203128,-0.00085030,-0.00103926,0.00061411,-0.00037791,0.00037791,-0.00108650,-0.00165337,-0.00245644,-0.00212576,-0.00099202,0.00080307,0.00207852,0.00264539,0.00321226,0.00340122,0.00510183,0.00581041,0.00689691,0.00566870,0.00363741,0.00155889,-0.00023620,-0.00018896,0.00014172,0.00075583,0.00066135,0.00042515,-0.00023620,0.00009448,-0.00014172,-0.00018896,-0.00061411,-0.00094478,-0.00108650,-0.00080307,-0.00014172,0.00056687,0.00193680,0.00264539,0.00264539,0.00141717,-0.00127546,-0.00410980,-0.00514907,-0.00486563,-0.00198404,0.00023620,0.00226748,0.00203128,0.00198404,0.00014172,0.00000000,-0.00165337,-0.00160613,-0.00146441,0.00004724,0.00151165,0.00273987,0.00302330,0.00226748,0.00240920,0.00160613,0.00179509,0.00103926,0.00023620,-0.00085030,-0.00170061,-0.00217300,-0.00311778,-0.00245644,-0.00259815,-0.00037791,0.00051963,0.00141717,0.00103926,-0.00047239,-0.00160613,-0.00429876,-0.00585765,-0.00873924,-0.00897544,-0.00869200,-0.00637728,-0.00349570,-0.00094478,0.00170061,0.00410980,0.00647176,0.00727483,0.00689691,0.00387361,0.00080307,-0.00193680,-0.00311778,-0.00434600,-0.00415704,-0.00481839,-0.00373189,-0.00264539,-0.00151165,-0.00160613,-0.00222024,-0.00368465,-0.00382637,-0.00467667,-0.00462944,-0.00538526,-0.00538526,-0.00477115,-0.00392085,-0.00240920,-0.00179509,-0.00160613,-0.00222024,-0.00307054,-0.00481839,-0.00581041,-0.00708587,-0.00651900,-0.00576317,-0.00401533,-0.00330674,-0.00245644,-0.00269263,-0.00222024,-0.00198404,-0.00127546,-0.00118098,-0.00160613,-0.00174785,-0.00231472,-0.00188957,-0.00141717,-0.00085030,0.00023620,0.00094478,0.00193680,0.00179509,0.00155889,-0.00042515,-0.00160613,-0.00288159,-0.00250367,-0.00103926,-0.00009448,0.00042515,-0.00080307,-0.00184233,-0.00165337,-0.00122822,0.00033067,-0.00080307,-0.00259815,-0.00477115,-0.00524354,-0.00340122,-0.00047239,0.00113374,0.00255091,0.00188957,0.00273987,0.00354294,0.00467667,0.00448772,0.00349570,0.00160613,-0.00004724,-0.00141717,-0.00240920,-0.00302330,-0.00188957,-0.00023620,0.00203128,0.00349570,0.00340122,0.00236196,0.00132270,0.00080307,0.00056687,0.00113374,0.00108650,0.00255091,0.00392085,0.00505459,0.00581041,0.00486563,0.00448772,0.00335398,0.00377913,0.00288159,0.00288159,0.00146441,0.00160613,0.00165337,0.00269263,0.00321226,0.00250367,0.00259815,0.00061411,0.00018896,-0.00170061,-0.00231472,-0.00240920,-0.00132270,0.00004724,0.00160613,0.00155889,0.00184233,0.00136993,0.00207852,0.00179509,0.00179509,-0.00037791,-0.00155889,-0.00387361,-0.00410980,-0.00514907,-0.00477115,-0.00552698,-0.00481839,-0.00538526,-0.00505459,-0.00538526,-0.00448772,-0.00222024,0.00170061,0.00557422,0.00793617,0.00803065,0.00543250,0.00307054,0.00089754,0.00051963,-0.00028343,0.00051963,-0.00075583,0.00061411,-0.00023620,0.00056687,-0.00080307,-0.00122822,-0.00302330,-0.00269263,-0.00316502,-0.00255091,-0.00330674,-0.00410980,-0.00510183,-0.00505459,-0.00434600,-0.00297607,-0.00165337,-0.00094478,-0.00004724,-0.00018896,-0.00018896,-0.00080307,-0.00118098,-0.00085030,-0.00004724,0.00089754,0.00222024,0.00193680,0.00240920,0.00136993,0.00094478,0.00028343,-0.00056687,-0.00113374,-0.00203128,-0.00222024,-0.00250367,-0.00174785,-0.00155889,0.00000000,-0.00023620,0.00113374,-0.00028343,0.00000000,-0.00141717,-0.00165337,-0.00236196,-0.00316502,-0.00363741,-0.00458220,-0.00410980,-0.00406257,-0.00307054,-0.00250367,-0.00226748,-0.00222024,-0.00250367,-0.00307054,-0.00340122,-0.00373189,-0.00401533,-0.00340122,-0.00273987,-0.00174785,-0.00089754,0.00004724,0.00080307,0.00222024,0.00207852,0.00325950,0.00122822,0.00160613,-0.00051963,-0.00108650,-0.00089754,-0.00250367,-0.00122822,-0.00273987,-0.00184233,-0.00198404,-0.00113374,-0.00047239,0.00000000,0.00037791,0.00051963,0.00089754,0.00127546,0.00170061,0.00203128,0.00273987,0.00297607,0.00359017,0.00335398,0.00255091,0.00222024,0.00170061,0.00245644,0.00292883,0.00335398,0.00349570,0.00302330,0.00297607,0.00222024,0.00113374,0.00028343,-0.00113374,-0.00113374,-0.00132270,-0.00042515,-0.00023620,0.00037791,0.00014172,0.00018896,-0.00033067,-0.00108650,-0.00170061,-0.00122822,-0.00080307,0.00070859,0.00089754,0.00080307,-0.00009448,-0.00066135,-0.00170061,-0.00212576,-0.00307054,-0.00330674,-0.00344846,-0.00226748,-0.00231472,-0.00094478,-0.00155889,-0.00056687,0.00014172,0.00151165,0.00269263,0.00297607,0.00264539,0.00212576,0.00212576,0.00160613,0.00226748,0.00122822,0.00151165,0.00113374,0.00212576,0.00307054,0.00401533,0.00467667,0.00472391,0.00477115,0.00505459,0.00458220,0.00354294,0.00236196,0.00004724,-0.00056687,-0.00141717,-0.00132270,-0.00136993,-0.00146441,-0.00141717,-0.00136993,-0.00099202,-0.00056687,0.00066135,0.00136993,0.00316502,0.00292883,0.00354294,0.00207852,0.00203128,0.00174785,0.00236196,0.00311778,0.00316502,0.00330674,0.00344846,0.00340122,0.00373189,0.00297607,0.00226748,0.00099202,0.00080307,0.00014172,0.00085030,-0.00108650,-0.00122822,-0.00321226,-0.00245644,-0.00203128,-0.00094478,-0.00014172,-0.00061411,-0.00042515,-0.00051963,0.00033067,0.00136993,0.00165337,0.00174785,-0.00004724,-0.00146441,-0.00505459,-0.00656624,-0.00864476,-0.00784170,-0.00651900,-0.00401533,-0.00193680,-0.00094478,-0.00014172,-0.00004724,-0.00023620,-0.00009448,-0.00122822,-0.00051963,-0.00014172,0.00127546,0.00146441,0.00085030,-0.00085030,-0.00231472,-0.00311778,-0.00382637,-0.00363741,-0.00420428,-0.00392085,-0.00297607,-0.00288159,-0.00179509,-0.00302330,-0.00292883,-0.00330674,-0.00222024,-0.00198404,-0.00051963,-0.00089754,0.00051963,0.00066135,0.00122822,-0.00018896,-0.00146441,-0.00368465,-0.00387361,-0.00377913,-0.00264539,-0.00170061,-0.00080307,-0.00023620,0.00047239,-0.00014172,-0.00108650,-0.00307054,-0.00349570,-0.00481839,-0.00340122,-0.00467667,-0.00505459,-0.00609385,-0.00684967,-0.00519630,-0.00406257,-0.00212576,-0.00136993,-0.00226748,-0.00240920,-0.00401533,-0.00373189,-0.00477115,-0.00448772,-0.00557422,-0.00496011,-0.00566870,-0.00481839,-0.00599937,-0.00524354,-0.00552698,-0.00321226,-0.00212576,0.00009448,-0.00028343,0.00080307,0.00018896,0.00174785,0.00103926,0.00089754,-0.00118098,-0.00255091,-0.00354294,-0.00292883,-0.00222024,-0.00141717,-0.00118098,-0.00160613,-0.00193680,-0.00231472,-0.00193680,-0.00094478,0.00042515,0.00245644,0.00250367,0.00217300,0.00051963,-0.00132270,-0.00207852,-0.00222024,-0.00193680,-0.00042515,0.00070859,0.00278711,0.00420428,0.00420428,0.00377913,0.00170061,-0.00014172,-0.00193680,-0.00396809,-0.00448772,-0.00453496,-0.00363741,-0.00184233,-0.00118098,-0.00075583,-0.00103926,-0.00122822,-0.00075583,-0.00037791,0.00023620,-0.00014172,0.00028343,-0.00037791,-0.00018896,-0.00108650,-0.00146441,-0.00193680,-0.00264539,-0.00132270,-0.00122822,0.00118098,0.00122822,0.00184233,0.00066135,-0.00033067,-0.00136993,-0.00170061,-0.00302330,-0.00340122,-0.00472391,-0.00425152,-0.00245644,-0.00004724,0.00222024,0.00311778,0.00311778,0.00269263,0.00203128,0.00165337,0.00070859,0.00042515,0.00028343,0.00051963,0.00080307,0.00014172,-0.00042515,-0.00132270,-0.00127546,-0.00061411,-0.00056687,-0.00014172,-0.00061411,-0.00028343,0.00018896,0.00136993,0.00193680,0.00273987,0.00269263,0.00269263,0.00273987,0.00245644,0.00250367,0.00151165,0.00099202,0.00070859,0.00160613,0.00311778,0.00401533,0.00363741,0.00141717,-0.00075583,-0.00259815,-0.00193680,-0.00146441,0.00023620,0.00000000,0.00061411,0.00066135,0.00222024,0.00269263,0.00354294,0.00302330,0.00222024,0.00113374,-0.00066135,-0.00198404,-0.00359017,-0.00307054,-0.00193680,0.00056687,0.00259815,0.00311778,0.00292883,0.00151165,0.00080307,-0.00042515,0.00004724,-0.00070859,-0.00009448,-0.00037791,-0.00051963,-0.00009448,0.00000000,0.00094478,0.00155889,0.00245644,0.00226748,0.00255091,0.00165337,0.00184233,0.00051963,0.00047239,-0.00108650,-0.00004724,-0.00023620,0.00080307,0.00037791,-0.00051963,-0.00146441,-0.00136993,-0.00037791,0.00160613,0.00297607,0.00373189,0.00340122,0.00236196,0.00122822,-0.00018896,-0.00066135,-0.00075583,0.00018896,0.00066135,0.00132270,0.00061411,0.00037791,-0.00023620,-0.00009448,-0.00070859,-0.00009448,-0.00165337,-0.00075583,-0.00193680,-0.00136993,-0.00288159,-0.00340122,-0.00467667,-0.00387361,-0.00377913,-0.00307054,-0.00292883,-0.00321226,-0.00231472,-0.00193680,-0.00066135,-0.00080307,-0.00118098,-0.00136993,-0.00155889,-0.00099202,-0.00141717,-0.00207852,-0.00278711,-0.00273987,-0.00188957,-0.00080307,-0.00014172,-0.00056687,-0.00099202,-0.00127546,-0.00155889,-0.00146441,-0.00222024,-0.00269263,-0.00264539,-0.00217300,-0.00033067,0.00099202,0.00165337,0.00240920,0.00165337,0.00203128,0.00141717,0.00099202,-0.00014172,-0.00089754,-0.00203128,-0.00170061,-0.00141717,-0.00037791,0.00004724,0.00004724,0.00047239,-0.00047239,0.00009448,-0.00103926,-0.00094478,-0.00174785,-0.00136993,-0.00080307,0.00028343,0.00070859,0.00136993,0.00056687,0.00047239,-0.00009448,-0.00042515,0.00018896,0.00051963,0.00066135,0.00160613,0.00118098,0.00226748,0.00311778,0.00396809,0.00496011,0.00429876,0.00373189,0.00273987,0.00245644,0.00250367,0.00278711,0.00349570,0.00377913,0.00434600,0.00486563,0.00472391,0.00491287,0.00354294,0.00344846,0.00165337,0.00217300,0.00165337,0.00373189,0.00462944,0.00628280,0.00609385,0.00496011,0.00396809,0.00226748,0.00226748,0.00245644,0.00273987,0.00278711,0.00212576,0.00085030,-0.00009448,-0.00184233,-0.00174785,-0.00231472,-0.00033067,0.00118098,0.00307054,0.00458220,0.00434600,0.00382637,0.00146441,-0.00014172,-0.00198404,-0.00179509,-0.00136993,0.00047239,0.00089754,0.00217300,0.00160613,0.00203128,0.00155889,0.00089754,0.00061411,0.00000000,0.00080307,0.00127546,0.00217300,0.00292883,0.00297607,0.00392085,0.00396809,0.00477115,0.00472391,0.00467667,0.00444048,0.00330674,0.00283435,0.00146441,0.00132270,0.00103926,0.00174785,0.00151165,0.00193680,0.00080307,0.00103926,0.00094478,0.00179509,0.00255091,0.00297607,0.00307054,0.00212576,0.00141717,-0.00033067,-0.00051963,-0.00160613,-0.00037791,0.00066135,0.00174785,0.00264539,0.00222024,0.00141717,0.00174785,0.00203128,0.00392085,0.00453496,0.00477115,0.00340122,0.00212576,0.00118098,0.00089754,0.00136993,0.00118098,0.00127546,0.00061411,0.00033067,-0.00009448,0.00009448,-0.00014172,0.00018896,0.00042515,0.00000000,-0.00009448,-0.00094478,-0.00122822,-0.00094478,0.00033067,0.00061411,0.00198404,0.00056687,-0.00009448,-0.00212576,-0.00368465,-0.00486563,-0.00585765,-0.00557422,-0.00524354,-0.00325950,-0.00174785,0.00037791,0.00118098,0.00089754,0.00018896,-0.00099202,-0.00070859,0.00004724,0.00155889,0.00212576,0.00231472,0.00151165,0.00089754,0.00023620,0.00056687,0.00070859,0.00236196,0.00340122,0.00538526,0.00585765,0.00694415,0.00562146,0.00552698,0.00363741,0.00321226,0.00184233,0.00160613,0.00146441,0.00207852,0.00226748,0.00222024,0.00132270,-0.00047239,-0.00179509,-0.00387361,-0.00359017,-0.00396809,-0.00141717,-0.00051963,0.00226748,0.00250367,0.00420428,0.00349570,0.00363741,0.00146441,-0.00061411,-0.00288159,-0.00392085,-0.00349570,-0.00179509,0.00023620,0.00146441,0.00311778,0.00288159,0.00401533,0.00250367,0.00212576,0.00014172,-0.00028343,-0.00051963,-0.00047239,0.00014172,-0.00037791,0.00004724,0.00014172,0.00009448,-0.00028343,-0.00222024,-0.00373189,-0.00557422,-0.00538526,-0.00496011,-0.00340122,-0.00217300,-0.00146441,-0.00061411,-0.00151165,-0.00146441,-0.00354294,-0.00335398,-0.00481839,-0.00363741,-0.00420428,-0.00359017,-0.00462944,-0.00491287,-0.00595213,-0.00590489,-0.00557422,-0.00486563,-0.00373189,-0.00344846,-0.00231472,-0.00179509,-0.00004724,0.00094478,0.00316502,0.00387361,0.00510183,0.00505459,0.00444048,0.00429876,0.00406257,0.00368465,0.00392085,0.00368465,0.00349570,0.00363741,0.00278711,0.00250367,0.00198404,0.00165337,0.00198404,0.00207852,0.00273987,0.00259815,0.00236196,0.00174785,0.00136993,0.00070859,0.00056687,0.00051963,0.00051963,0.00127546,0.00146441,0.00160613,0.00170061,0.00042515,-0.00009448,-0.00108650,-0.00188957,-0.00203128,-0.00278711,-0.00193680,-0.00217300,-0.00160613,-0.00207852,-0.00245644,-0.00311778,-0.00297607,-0.00307054,-0.00132270,-0.00160613,-0.00023620,-0.00094478,-0.00004724,0.00037791,0.00089754,0.00094478,-0.00089754,-0.00193680,-0.00330674,-0.00316502,-0.00207852,-0.00085030,0.00018896,0.00103926,0.00155889,0.00203128,0.00212576,0.00207852,0.00070859,0.00103926,-0.00023620,0.00014172,-0.00122822,-0.00155889,-0.00174785,-0.00075583,0.00037791,0.00113374,0.00042515,-0.00042515,-0.00151165,-0.00141717,-0.00075583,-0.00018896,0.00014172,0.00056687,0.00094478,0.00207852,0.00311778,0.00377913,0.00448772,0.00472391,0.00547974,0.00562146,0.00557422,0.00415704,0.00359017,0.00259815,0.00382637,0.00382637,0.00429876,0.00349570,0.00155889,0.00155889,0.00004724,0.00151165,0.00118098,0.00212576,0.00245644,0.00340122,0.00429876,0.00491287,0.00429876,0.00321226,0.00146441,-0.00004724,-0.00033067,-0.00103926,-0.00047239,-0.00051963,-0.00042515,0.00051963,0.00066135,0.00132270,0.00155889,0.00103926,0.00151165,0.00170061,0.00222024,0.00307054,0.00250367,0.00222024,0.00070859,-0.00009448,-0.00103926,-0.00085030,-0.00118098,-0.00099202,-0.00165337,-0.00099202,-0.00075583,0.00108650,0.00212576,0.00340122,0.00406257,0.00453496,0.00496011,0.00524354,0.00462944,0.00429876,0.00349570,0.00406257,0.00477115,0.00571594,0.00595213,0.00486563,0.00302330,0.00122822,-0.00033067,0.00033067,0.00127546,0.00307054,0.00434600,0.00462944,0.00354294,0.00255091,0.00070859,0.00023620,-0.00070859,-0.00080307,-0.00231472,-0.00160613,-0.00288159,-0.00151165,-0.00179509,-0.00094478,-0.00028343,0.00094478,0.00217300,0.00340122,0.00368465,0.00363741,0.00222024,0.00198404,0.00037791,0.00014172,-0.00099202,-0.00099202,-0.00099202,-0.00047239,-0.00042515,-0.00023620,-0.00089754,-0.00108650,-0.00146441,-0.00118098,-0.00099202,-0.00080307,-0.00099202,-0.00151165,-0.00226748,-0.00231472,-0.00217300,-0.00094478,0.00023620,0.00056687,0.00070859,0.00009448,-0.00028343,0.00056687,0.00103926,0.00278711,0.00316502,0.00406257,0.00382637,0.00344846,0.00278711,0.00155889,0.00122822,0.00080307,0.00174785,0.00198404,0.00273987,0.00184233,0.00094478,0.00042515,-0.00009448,0.00042515,0.00122822,0.00132270,0.00212576,0.00226748,0.00236196,0.00259815,0.00136993,0.00033067,-0.00108650,-0.00198404,-0.00184233,-0.00174785,-0.00151165,-0.00174785,-0.00179509,-0.00179509,-0.00042515,-0.00014172,0.00075583,0.00037791,0.00047239,0.00103926,0.00212576,0.00273987,0.00401533,0.00410980,0.00491287,0.00491287,0.00538526,0.00453496,0.00481839,0.00325950,0.00231472,0.00061411,-0.00136993,-0.00240920,-0.00316502,-0.00226748,-0.00113374,0.00037791,0.00193680,0.00245644,0.00368465,0.00359017,0.00429876,0.00420428,0.00444048,0.00434600,0.00429876,0.00434600,0.00472391,0.00500735,0.00543250,0.00590489,0.00543250,0.00538526,0.00448772,0.00377913,0.00297607,0.00165337,0.00080307,0.00023620,0.00042515,0.00207852,0.00325950,0.00434600,0.00392085,0.00292883,0.00165337,0.00179509,0.00179509,0.00288159,0.00264539,0.00269263,0.00245644,0.00273987,0.00325950,0.00344846,0.00278711,0.00141717,-0.00004724,0.00018896,0.00023620,0.00344846,0.00467667,0.00732207,0.00769998,0.00675520,0.00519630,0.00335398,0.00222024,0.00212576,0.00146441,0.00099202,0.00000000,-0.00122822,-0.00188957,-0.00288159,-0.00307054,-0.00335398,-0.00344846,-0.00292883,-0.00292883,-0.00217300,-0.00264539,-0.00240920,-0.00302330,-0.00297607,-0.00344846,-0.00321226,-0.00321226,-0.00132270,-0.00061411,0.00160613,0.00179509,0.00236196,0.00184233,0.00207852,0.00132270,0.00146441,0.00094478,0.00127546,0.00236196,0.00481839,0.00637728,0.00878648,0.00930611,0.00916439,0.00855028,0.00703863,0.00604661,0.00533802,0.00529078,0.00552698,0.00666072,0.00779446,0.00873924,0.00883372,0.00803065,0.00571594,0.00396809,0.00269263,0.00283435,0.00439324,0.00519630,0.00581041,0.00472391,0.00377913,0.00207852,0.00198404,0.00141717,0.00240920,0.00410980,0.00519630,0.00633004,0.00486563,0.00311778,-0.00018896,-0.00146441,-0.00354294,-0.00188957,-0.00217300,0.00004724,0.00028343,0.00146441,0.00198404,0.00231472,0.00292883,0.00354294,0.00491287,0.00533802,0.00656624,0.00576317,0.00599937,0.00453496,0.00429876,0.00316502,0.00359017,0.00382637,0.00415704,0.00420428,0.00316502,0.00188957,0.00085030,0.00047239,0.00056687,0.00203128,0.00255091,0.00420428,0.00458220,0.00543250,0.00524354,0.00552698,0.00510183,0.00505459,0.00410980,0.00349570,0.00141717,0.00004724,-0.00174785,-0.00198404,-0.00193680,-0.00037791,0.00056687,0.00184233,0.00240920,0.00297607,0.00245644,0.00283435,0.00184233,0.00222024,0.00193680,0.00283435,0.00297607,0.00269263,0.00273987,0.00179509,0.00236196,0.00292883,0.00311778,0.00392085,0.00193680,0.00127546,-0.00085030,-0.00160613,-0.00136993,-0.00099202,0.00028343,0.00066135,0.00014172,-0.00099202,-0.00259815,-0.00349570,-0.00429876,-0.00359017,-0.00363741,-0.00236196,-0.00198404,-0.00089754,-0.00042515,0.00009448,0.00037791,0.00066135,0.00066135,0.00080307,-0.00037791,-0.00113374,-0.00292883,-0.00368465,-0.00425152,-0.00401533,-0.00325950,-0.00255091,-0.00056687,0.00014172,0.00193680,0.00127546,0.00080307,-0.00113374,-0.00203128,-0.00344846,-0.00363741,-0.00415704,-0.00429876,-0.00420428,-0.00363741,-0.00288159,-0.00231472,-0.00236196,-0.00288159,-0.00283435,-0.00222024,-0.00118098,0.00042515,0.00023620,0.00118098,-0.00004724,0.00066135,0.00009448,0.00070859,0.00089754,0.00155889,0.00184233,0.00240920,0.00184233,0.00155889,0.00094478,0.00028343,0.00075583,0.00033067,0.00037791,0.00018896,0.00047239,0.00122822,0.00231472,0.00264539,0.00240920,0.00174785,0.00094478,0.00018896,-0.00033067,-0.00099202,-0.00165337,-0.00113374,-0.00108650,0.00051963,0.00042515,0.00085030,0.00037791,-0.00018896,-0.00018896,-0.00122822,-0.00108650,-0.00170061,-0.00103926,-0.00051963,0.00028343,0.00070859,0.00075583,0.00051963,0.00037791,0.00009448,0.00000000,0.00000000,0.00051963,0.00136993,0.00255091,0.00316502,0.00373189,0.00288159,0.00283435,0.00127546,0.00085030,-0.00094478,-0.00203128,-0.00396809,-0.00458220,-0.00477115,-0.00382637,-0.00198404,-0.00037791,0.00047239,0.00075583,0.00051963,0.00070859,0.00103926,0.00207852,0.00207852,0.00273987,0.00255091,0.00288159,0.00302330,0.00250367,0.00122822,-0.00061411,-0.00217300,-0.00273987,-0.00250367,-0.00184233,-0.00141717,-0.00080307,-0.00042515,0.00080307,0.00146441,0.00217300,0.00179509,0.00085030,0.00042515,-0.00066135,0.00009448,-0.00127546,-0.00103926,-0.00292883,-0.00349570,-0.00453496,-0.00496011,-0.00519630,-0.00472391,-0.00377913,-0.00236196,-0.00018896,0.00047239,0.00070859,-0.00070859,-0.00307054,-0.00538526,-0.00628280,-0.00651900,-0.00373189,-0.00099202,0.00283435,0.00533802,0.00769998,0.00821961,0.00892820,0.00736931,0.00486563,0.00146441,-0.00344846,-0.00585765,-0.00840857,-0.00798341,-0.00727483,-0.00529078,-0.00344846,-0.00118098,0.00004724,0.00085030,0.00023620,-0.00023620,-0.00127546,-0.00170061,-0.00174785,-0.00184233,-0.00174785,-0.00132270,-0.00179509,-0.00179509,-0.00255091,-0.00283435,-0.00292883,-0.00231472,-0.00217300,-0.00155889,-0.00179509,-0.00108650,-0.00080307,0.00042515,0.00132270,0.00240920,0.00222024,0.00103926,-0.00118098,-0.00396809,-0.00524354,-0.00576317,-0.00434600,-0.00387361,-0.00311778,-0.00439324,-0.00458220,-0.00462944,-0.00302330,-0.00103926,0.00061411,0.00099202,0.00051963,-0.00051963,-0.00141717,-0.00174785,-0.00174785,-0.00108650,-0.00103926,-0.00047239,-0.00099202,-0.00089754,-0.00089754,-0.00127546,-0.00136993,-0.00288159,-0.00307054,-0.00519630,-0.00519630,-0.00666072,-0.00604661,-0.00661348,-0.00590489,-0.00651900,-0.00595213,-0.00604661,-0.00448772,-0.00387361,-0.00255091,-0.00321226,-0.00330674,-0.00354294,-0.00236196,-0.00174785,-0.00066135,-0.00179509,-0.00217300,-0.00330674,-0.00231472,-0.00165337,0.00080307,0.00193680,0.00377913,0.00444048,0.00387361,0.00236196,-0.00033067,-0.00278711,-0.00462944,-0.00614109,-0.00718035,-0.00741654,-0.00675520,-0.00453496,-0.00259815,-0.00118098,-0.00122822,-0.00292883,-0.00368465,-0.00500735,-0.00547974,-0.00623557,-0.00694415,-0.00694415,-0.00642452,-0.00524354,-0.00486563,-0.00462944,-0.00529078,-0.00491287,-0.00481839,-0.00344846,-0.00302330,-0.00198404,-0.00174785,-0.00198404,-0.00165337,-0.00273987,-0.00231472,-0.00207852,-0.00108650,-0.00009448,0.00056687,0.00042515,0.00014172,-0.00070859,-0.00179509,-0.00288159,-0.00377913,-0.00519630,-0.00566870,-0.00604661,-0.00604661,-0.00486563,-0.00462944,-0.00363741,-0.00340122,-0.00311778,-0.00250367,-0.00207852,-0.00136993,-0.00127546,-0.00089754,-0.00033067,0.00037791,0.00094478,0.00070859,-0.00042515,-0.00188957,-0.00269263,-0.00340122,-0.00316502,-0.00292883,-0.00255091,-0.00165337,-0.00193680,-0.00198404,-0.00406257,-0.00529078,-0.00694415,-0.00736931,-0.00699139,-0.00609385,-0.00434600,-0.00236196,-0.00037791,0.00085030,0.00155889,0.00207852,0.00288159,0.00439324,0.00467667,0.00538526,0.00321226,0.00212576,0.00018896,-0.00108650,-0.00132270,-0.00217300,-0.00170061,-0.00179509,-0.00122822,-0.00127546,-0.00118098,-0.00146441,-0.00151165,-0.00231472,-0.00368465,-0.00491287,-0.00651900,-0.00647176,-0.00680244,-0.00595213,-0.00505459,-0.00349570,-0.00170061,-0.00037791,-0.00009448,-0.00118098,-0.00212576,-0.00382637,-0.00377913,-0.00415704,-0.00382637,-0.00302330,-0.00217300,0.00009448,0.00170061,0.00349570,0.00349570,0.00392085,0.00292883,0.00283435,0.00127546,-0.00108650,-0.00410980,-0.00821961,-0.01029813,-0.01209322,-0.01043985,-0.00779446,-0.00396809,0.00018896,0.00240920,0.00500735,0.00491287,0.00581041,0.00425152,0.00321226,0.00132270,0.00000000,-0.00113374,-0.00170061,-0.00311778,-0.00288159,-0.00368465,-0.00250367,-0.00217300,-0.00184233,-0.00132270,-0.00127546,0.00009448,0.00033067,0.00028343,-0.00198404,-0.00316502,-0.00585765,-0.00510183,-0.00595213,-0.00392085,-0.00307054,-0.00051963,-0.00028343,0.00075583,-0.00070859,-0.00023620,-0.00056687,0.00108650,0.00127546,0.00184233,-0.00066135,-0.00269263,-0.00760550,-0.01232941,-0.01691161,-0.01780915,-0.01450241,-0.00689691,0.00033067,0.00415704,0.00458220,0.00288159,0.00321226,0.00500735,0.00774722,0.00798341,0.00670796,0.00340122,0.00122822,-0.00179509,-0.00387361,-0.00769998,-0.01081776,-0.01365211,-0.01492757,-0.01398278,-0.01232941,-0.00973126,-0.00864476,-0.00925887,-0.01266009,-0.01653370,-0.02012387,-0.02050178,-0.01960424,-0.01620302,-0.01256561,-0.00736931,-0.00193680,0.00354294,0.00774722,0.01039261,0.01171531,0.01346315,0.01483309,0.01747848,0.01899013,0.02050178,0.02002939,0.01865946,0.01530548,0.01100672,0.00618833,0.00160613,-0.00198404,-0.00491287,-0.00680244,-0.00736931,-0.00708587,-0.00500735,-0.00472391,-0.00533802,-0.00987298,-0.01629750,-0.02442263,-0.03174470,-0.03519316,-0.03434285,-0.02569809,-0.01412450,0.00075583,0.01138463,0.01856498,0.01880118,0.01667541,0.01327420,0.01138463,0.01124291,0.01195150,0.01322696,0.01521100,0.01809259,0.02135209,0.02390300,0.02253307,0.01823431,0.00973126,0.00018896,-0.01006194,-0.02026559,-0.02895759,-0.03443733,-0.03396494,-0.02602876,-0.01384107,-0.00089754,0.00836133,0.01280181,0.01568339,0.01691161,0.01790363,0.01573063,0.01043985,0.00387361,-0.00316502,-0.00661348,-0.01010917,-0.01062881,-0.01166807,-0.01114844,-0.00996746,-0.01034537,-0.01180978,-0.01549444,-0.01894289,-0.02059626,-0.02083246,-0.01823431,-0.01601407,-0.01270733,-0.01086500,-0.01119567,-0.01256561,-0.01506928,-0.01421898,-0.01133739,-0.00798341,-0.00821961,-0.01431346,-0.02404472,-0.03363426,-0.03935020,-0.03906676,-0.03131955,-0.01634474,0.00557422,0.02957170,0.04875079,0.05701764,0.05309679,0.04133424,0.02942998,0.02102142,0.01648646,0.01289628,0.00736931,0.00231472,-0.00188957,-0.00321226,-0.00392085,-0.00420428,-0.00708587,-0.00736931,-0.00892820,-0.00680244,-0.00491287,-0.00255091,-0.00051963,0.00099202,0.00155889,0.00179509,-0.00028343,-0.00198404,-0.00524354,-0.00670796,-0.00680244,-0.00453496,0.00009448,0.00562146,0.01025089,0.01346315,0.01469137,0.01317972,0.01266009,0.01025089,0.00977850,0.00921163,0.00944783,0.01001470,0.01062881,0.01062881,0.01058157,0.01006194,0.00892820,0.00784170,0.00486563,0.00207852,-0.00174785,-0.00396809,-0.00661348,-0.00666072,-0.00736931,-0.00571594,-0.00439324,-0.00174785,0.00066135,0.00363741,0.00529078,0.00633004,0.00552698,0.00387361,0.00236196,0.00184233,0.00278711,0.00467667,0.00618833,0.00699139,0.00680244,0.00547974,0.00392085,0.00023620,-0.00316502,-0.00765274,-0.01095948,-0.01303800,-0.01488033,-0.01516376,-0.01563615,-0.01351039,-0.01110120,-0.00675520,-0.00354294,-0.00061411,0.00231472,0.00472391,0.00732207,0.00855028,0.00793617,0.00599937,0.00330674,-0.00033067,-0.00292883,-0.00609385,-0.00821961,-0.00921163,-0.00968402,-0.00864476,-0.00703863,-0.00491287,-0.00259815,-0.00047239,-0.00004724,0.00028343,-0.00146441,-0.00188957,-0.00349570,-0.00368465,-0.00538526,-0.00623557,-0.00755826,-0.00855028,-0.00996746,-0.01176254,-0.01365211,-0.01563615,-0.01634474,-0.01634474,-0.01568339,-0.01336868,-0.01081776,-0.00727483,-0.00354294,-0.00207852,-0.00089754,-0.00222024,-0.00193680,-0.00269263,-0.00132270,-0.00141717,-0.00146441,-0.00179509,-0.00340122,-0.00349570,-0.00519630,-0.00458220,-0.00500735,-0.00387361,-0.00349570,-0.00283435,-0.00307054,-0.00259815,-0.00307054,-0.00344846,-0.00392085,-0.00467667,-0.00396809,-0.00288159,-0.00165337,-0.00122822,-0.00118098,-0.00193680,-0.00099202,-0.00127546,-0.00061411,-0.00203128,-0.00259815,-0.00444048,-0.00387361,-0.00467667,-0.00401533,-0.00368465,-0.00283435,-0.00151165,-0.00037791,0.00014172,0.00047239,0.00141717,0.00217300,0.00387361,0.00514907,0.00491287,0.00552698,0.00434600,0.00382637,0.00307054,0.00179509,0.00179509,0.00146441,0.00288159,0.00363741,0.00609385,0.00703863,0.00925887,0.00944783,0.00987298,0.00902267,0.00788894,0.00694415,0.00609385,0.00547974,0.00448772,0.00406257,0.00335398,0.00420428,0.00543250,0.00699139,0.00812513,0.00727483,0.00566870,0.00269263,0.00033067,-0.00151165,-0.00165337,-0.00103926,0.00056687,0.00273987,0.00425152,0.00571594,0.00642452,0.00722759,0.00902267,0.01081776,0.01308524,0.01317972,0.01237665,0.01025089,0.00798341,0.00642452,0.00429876,0.00170061,-0.00226748,-0.00590489,-0.00906991,-0.01081776,-0.01114844,-0.01081776,-0.00925887,-0.00788894,-0.00670796,-0.00637728,-0.00656624,-0.00628280,-0.00453496,-0.00316502,-0.00099202,-0.00018896,0.00061411,0.00165337,0.00198404,0.00226748,0.00184233,0.00217300,0.00349570,0.00533802,0.00765274,0.00831409,0.00963678,0.00968402,0.01015641,0.00878648,0.00817237,0.00708587,0.00954231,0.01171531,0.01289628,0.01129015,0.00581041,-0.00047239,-0.00755826,-0.01284904,-0.01535272,-0.01242389,-0.00368465,0.00618833,0.01266009,0.01006194,0.00203128,-0.00543250,-0.00831409,-0.00746378,-0.00992022,-0.01780915,-0.02758765,-0.03160298,-0.02555637,-0.01072328,0.00425152,0.01691161,0.02262755,0.02428092,0.02333613,0.02319442,0.02971342,0.04289313,0.05777346,0.06084401,0.04133424,0.00056687,-0.04421583,-0.07425992,-0.07459059,-0.05380537,-0.02276926,0.00207852,0.01643922,0.02201344,0.02087970,0.01695885,0.00996746,0.00359017,-0.00217300,-0.00637728,-0.01086500,-0.01445518,-0.01743124,-0.01752572,-0.01747848,-0.01889565,-0.02234411,-0.02650115,-0.02862692,-0.02815452,-0.02579257,-0.02309994,-0.02064350,-0.01955700,-0.02154105,-0.02749318,-0.03443733,-0.03831094,-0.03387046,-0.02489502,-0.01558891,-0.01266009,-0.01398278,-0.01488033,-0.01237665,-0.00552698,-0.00118098,0.00222024,0.00222024,0.00373189,0.00434600,0.00325950,-0.00151165,-0.00718035,-0.01077052,-0.01100672,-0.00760550,-0.00359017,0.00340122,0.01176254,0.02173000,0.02806005,0.03070544,0.02829624,0.02654839,0.02470607,0.02494226,0.02338337,0.02144657,0.02007663,0.02050178,0.02276926,0.02489502,0.02565085,0.02390300,0.01771468,0.00694415,-0.00760550,-0.01884841,-0.02050178,-0.00968402,0.00987298,0.02886311,0.04034222,0.04142872,0.03505144,0.02517846,0.01672265,0.01218770,0.01110120,0.01275457,0.01384107,0.01861222,0.02801281,0.04568024,0.06159983,0.06155259,0.03609070,-0.01143187,-0.05800966,-0.08370775,-0.07789733,-0.05252992,-0.02319442,-0.00085030,0.01398278,0.02650115,0.03646861,0.03925572,0.03514592,0.02654839,0.02130485,0.02121037,0.02210792,0.02069074,0.01544720,0.00680244,-0.00401533,-0.01941528,-0.03670481,-0.04922318,-0.04955385,-0.03760235,-0.02059626,-0.00798341,-0.00316502,-0.00066135,0.00179509,0.00288159,-0.00245644,-0.01757296,-0.03278396,-0.04242074,-0.04067290,-0.03349255,-0.02711526,-0.02607600,-0.02994961,-0.03897229,-0.04889250,-0.05564770,-0.04818392,-0.01932081,0.02347785,0.06485933,0.08210162,0.07095318,0.03873609,0.00514907,-0.01861222,-0.03065820,-0.03292568,-0.02994961,-0.01861222,-0.00269263,0.01445518,0.02489502,0.03098887,0.03420113,0.04081461,0.04903422,0.05413605,0.05479740,0.05238820,0.05115998,0.05167961,0.04979005,0.04341277,0.03259500,0.02371405,0.01780915,0.01634474,0.01336868,0.00987298,0.00524354,0.00354294,0.00481839,0.00751102,0.01001470,0.01081776,0.01095948,0.00977850,0.00784170,0.00439324,0.00089754,-0.00325950,-0.00661348,-0.01058157,-0.01228218,-0.01317972,-0.01053433,-0.00954231,-0.01015641,-0.01426622,-0.01903737,-0.02130485,-0.02045455,-0.01818707,-0.01601407,-0.01403002,-0.01218770,-0.00746378,-0.00330674,0.00193680,0.00765274,0.01478585,0.02130485,0.02437539,0.01936805,0.01086500,0.00604661,0.01266009,0.03250052,0.05640353,0.07298446,0.07388201,0.05749003,0.02990237,-0.00288159,-0.03212261,-0.05309679,-0.05904892,-0.04936490,-0.02886311,-0.00335398,0.01710057,0.03207537,0.04057842,0.04506613,0.04530233,0.04175940,0.03405942,0.02654839,0.02059626,0.01648646,0.01176254,0.00496011,-0.00179509,-0.00562146,-0.00302330,0.00288159,0.00949507,0.01270733,0.01303800,0.01166807,0.01171531,0.01204598,0.01341591,0.01365211,0.01171531,0.00755826,-0.00004724,-0.00916439,-0.01804535,-0.02480055,-0.02824900,-0.02957170,-0.03013857,-0.03103611,-0.03216985,-0.03434285,-0.03538211,-0.03736616,-0.03689376,-0.03490972,-0.03018581,-0.02494226,-0.01988768,-0.01676989,-0.01483309,-0.01294352,-0.01114844,-0.00864476,-0.00741654,-0.00670796,-0.00689691,-0.00656624,-0.00585765,-0.00255091,0.00018896,0.00576317,0.00954231,0.01369935,0.01563615,0.01705333,0.01733676,0.01766744,0.01766744,0.01676989,0.01497481,0.01223494,0.00883372,0.00618833,0.00406257,0.00401533,0.00387361,0.00340122,0.00141717,-0.00018896,-0.00018896,0.00514907,0.01114844,0.01828155,0.01903737,0.01478585,0.00581041,-0.00349570,-0.01081776,-0.01407726,-0.01336868,-0.01015641,-0.00491287,-0.00089754,0.00198404,0.00226748,0.00184233,0.00203128,0.00250367,0.00434600,0.00500735,0.00628280,0.00680244,0.00803065,0.00826685,0.00675520,0.00472391,0.00136993,-0.00080307,-0.00292883,-0.00429876,-0.00642452,-0.00736931,-0.00803065,-0.00703863,-0.00656624,-0.00623557,-0.00727483,-0.00873924,-0.00992022,-0.01209322,-0.01322696,-0.01521100,-0.01563615,-0.01488033,-0.01346315,-0.01143187,-0.01043985,-0.00949507,-0.00873924,-0.00803065,-0.00722759,-0.00680244,-0.00595213,-0.00368465,0.00056687,0.00538526,0.01039261,0.01242389,0.01289628,0.01110120,0.00869200,0.00581041,0.00340122,0.00146441,0.00085030,0.00132270,0.00188957,0.00184233,0.00004724,-0.00292883,-0.00486563,-0.00538526,-0.00198404,0.00316502,0.00982574,0.01488033,0.01743124,0.01714781,0.01445518,0.01119567,0.00878648,0.00628280,0.00623557,0.00529078,0.00599937,0.00590489,0.00543250,0.00373189,0.00056687,-0.00292883,-0.00514907,-0.00519630,-0.00292883,0.00132270,0.00410980,0.00826685,0.01006194,0.01327420,0.01473861,0.01497481,0.01317972,0.00996746,0.00642452,0.00401533,0.00146441,-0.00018896,-0.00259815,-0.00491287,-0.00618833,-0.00788894,-0.00713311,-0.00765274,-0.00642452,-0.00604661,-0.00566870,-0.00505459,-0.00543250,-0.00410980,-0.00278711,0.00033067,0.00283435,0.00519630,0.00633004,0.00684967,0.00736931,0.00718035,0.00798341,0.00713311,0.00741654,0.00599937,0.00614109,0.00486563,0.00467667,0.00344846,0.00255091,0.00061411,-0.00217300,-0.00519630,-0.00703863,-0.00628280,-0.00118098,0.00510183,0.01294352,0.01620302,0.01672265,0.01289628,0.00949507,0.00642452,0.00429876,0.00141717,-0.00340122,-0.00807789,-0.01180978,-0.01095948,-0.00873924,-0.00377913,-0.00212576,-0.00165337,-0.00325950,-0.00557422,-0.00642452,-0.00732207,-0.00713311,-0.00675520,-0.00585765,-0.00448772,-0.00217300,-0.00122822,0.00037791,-0.00170061,-0.00496011,-0.01034537,-0.01412450,-0.01431346,-0.00859752,-0.00118098,0.00713311,0.01053433,0.01043985,0.00727483,0.00307054,-0.00127546,-0.00533802,-0.00850304,-0.00892820,-0.00647176,-0.00188957,0.00240920,0.00406257,0.00325950,0.00028343,-0.00212576,-0.00609385,-0.00784170,-0.01015641,-0.00930611,-0.00637728,-0.00231472,0.00184233,0.00344846,0.00184233,-0.00151165,-0.00732207,-0.01313248,-0.01875394,-0.02210792,-0.02319442,-0.02125761,-0.01889565,-0.01530548,-0.01289628,-0.01029813,-0.00944783,-0.00968402,-0.01280181,-0.01530548,-0.01832878,-0.01757296,-0.01587235,-0.01218770,-0.00906991,-0.00651900,-0.00481839,-0.00410980,-0.00472391,-0.00647176,-0.00826685,-0.00968402,-0.00996746,-0.00864476,-0.00821961,-0.00595213,-0.00505459,-0.00316502,-0.00160613,-0.00113374,-0.00018896,-0.00066135,0.00132270,0.00188957,0.00439324,0.00448772,0.00477115,0.00335398,0.00340122,0.00382637,0.00647176,0.00925887,0.01266009,0.01379383,0.01450241,0.01270733,0.01133739,0.00949507,0.00935335,0.01029813,0.01341591,0.01676989,0.02021835,0.02206068,0.02092694,0.01818707,0.01355763,0.01067604,0.00845581,0.00873924,0.00954231,0.01110120,0.01209322,0.01322696,0.01185702,0.01043985,0.00595213,0.00335398,0.00051963,0.00094478,0.00222024,0.00325950,0.00415704,0.00410980,0.00429876,0.00462944,0.00387361,0.00226748,-0.00146441,-0.00406257,-0.00633004,-0.00585765,-0.00387361,-0.00160613,0.00103926,0.00240920,0.00325950,0.00302330,0.00174785,-0.00023620,-0.00236196,-0.00533802,-0.00675520,-0.00982574,-0.01043985,-0.01110120,-0.01072328,-0.00873924,-0.00864476,-0.00793617,-0.01006194,-0.01180978,-0.01445518,-0.01568339,-0.01629750,-0.01568339,-0.01483309,-0.01327420,-0.01209322,-0.01048709,-0.00788894,-0.00458220,-0.00023620,0.00335398,0.00533802,0.00566870,0.00425152,0.00250367,-0.00023620,-0.00264539,-0.00505459,-0.00496011,-0.00259815,0.00250367,0.00727483,0.01072328,0.01110120,0.00902267,0.00769998,0.00462944,0.00359017,0.00004724,-0.00330674,-0.00755826,-0.01081776,-0.01294352,-0.01450241,-0.01436070,-0.01421898,-0.01228218,-0.01010917,-0.00703863,-0.00496011,-0.00302330,-0.00250367,-0.00198404,-0.00118098,-0.00037791,0.00009448,-0.00037791,-0.00264539,-0.00604661,-0.00902267,-0.01067604,-0.00996746,-0.00670796,-0.00448772,-0.00264539,-0.00429876,-0.00925887,-0.01610855,-0.02498950,-0.03221709,-0.03623242,-0.03391770,-0.02683183,-0.01492757,-0.00458220,0.00448772,0.00755826,0.00935335,0.00850304,0.00855028,0.00821961,0.00599937,0.00335398,-0.00165337,-0.00453496,-0.00576317,-0.00401533,0.00066135,0.00552698,0.01072328,0.01403002,0.01549444,0.01473861,0.01393554,0.01266009,0.01454965,0.01577787,0.01809259,0.01710057,0.01483309,0.01114844,0.00779446,0.00609385,0.00458220,0.00415704,0.00311778,0.00349570,0.00325950,0.00514907,0.00481839,0.00609385,0.00496011,0.00462944,0.00363741,0.00264539,0.00236196,0.00250367,0.00448772,0.00656624,0.00935335,0.01110120,0.01232941,0.01346315,0.01346315,0.01369935,0.01190426,0.01001470,0.00623557,0.00330674,0.00004724,-0.00207852,-0.00259815,-0.00316502,-0.00170061,-0.00184233,-0.00103926,-0.00179509,-0.00141717,-0.00108650,-0.00018896,0.00018896,-0.00051963,-0.00165337,-0.00297607,-0.00392085,-0.00425152,-0.00552698,-0.00604661,-0.00859752,-0.01010917,-0.01176254,-0.01223494,-0.01081776,-0.00869200,-0.00538526,-0.00269263,-0.00174785,-0.00132270,-0.00363741,-0.00481839,-0.00760550,-0.00940059,-0.01157359,-0.01261285,-0.01261285,-0.01062881,-0.00751102,-0.00330674,0.00037791,0.00354294,0.00481839,0.00529078,0.00486563,0.00477115,0.00547974,0.00661348,0.00722759,0.00699139,0.00491287,0.00354294,0.00212576,0.00269263,0.00429876,0.00576317,0.00651900,0.00547974,0.00340122,0.00132270,-0.00018896,-0.00113374,-0.00165337,-0.00226748,-0.00283435,-0.00297607,-0.00231472,-0.00155889,-0.00028343,-0.00023620,0.00042515,0.00099202,0.00203128,0.00325950,0.00250367,0.00136993,-0.00118098,-0.00297607,-0.00335398,-0.00307054,-0.00165337,-0.00099202,-0.00009448,0.00080307,0.00089754,0.00198404,0.00113374,0.00184233,0.00132270,0.00165337,0.00061411,-0.00051963,-0.00212576,-0.00231472,-0.00165337,0.00047239,0.00273987,0.00496011,0.00694415,0.00760550,0.00845581,0.00684967,0.00529078,0.00302330,0.00136993,0.00160613,0.00118098,0.00085030,-0.00075583,-0.00288159,-0.00392085,-0.00401533,-0.00259815,-0.00113374,-0.00037791,0.00000000,-0.00155889,-0.00448772,-0.00963678,-0.01639198,-0.02149381,-0.02357233,-0.01974596,-0.01209322,-0.00292883,0.00377913,0.00666072,0.00562146,0.00297607,-0.00056687,-0.00368465,-0.00666072,-0.01001470,-0.01223494,-0.01384107,-0.01431346,-0.01365211,-0.01242389,-0.01077052,-0.00944783,-0.00883372,-0.01114844,-0.01516376,-0.02069074,-0.02532018,-0.02664287,-0.02343061,-0.01747848,-0.00940059,-0.00236196,0.00283435,0.00552698,0.00566870,0.00349570,0.00000000,-0.00330674,-0.00552698,-0.00661348,-0.00519630,-0.00444048,-0.00264539,-0.00217300,-0.00269263,-0.00344846,-0.00618833,-0.00803065,-0.01048709,-0.01053433,-0.00906991,-0.00684967,-0.00316502,-0.00118098,0.00108650,0.00226748,0.00231472,0.00222024,0.00075583,-0.00042515,-0.00103926,-0.00108650,0.00108650,0.00198404,0.00467667,0.00453496,0.00524354,0.00543250,0.00552698,0.00722759,0.00751102,0.00675520,0.00354294,-0.00217300,-0.00977850,-0.01790363,-0.02607600,-0.03188642,-0.03358702,-0.02957170,-0.01932081,-0.00581041,0.00845581,0.01691161,0.01894289,0.01242389,0.00113374,-0.01232941,-0.02324165,-0.02876863,-0.02692631,-0.01974596,-0.00774722,0.00354294,0.01417174,0.02135209,0.02376128,0.02300546,0.01681713,0.00930611,0.00051963,-0.00595213,-0.01034537,-0.01209322,-0.01261285,-0.01232941,-0.01105396,-0.00921163,-0.00718035,-0.00491287,-0.00377913,-0.00231472,-0.00118098,0.00155889,0.00396809,0.00784170,0.00977850,0.01062881,0.00769998,0.00188957,-0.00566870,-0.01275457,-0.01738400,-0.01880118,-0.01780915,-0.01417174,-0.00878648,-0.00122822,0.00618833,0.01119567,0.01114844,0.00675520,-0.00042515,-0.00628280,-0.01001470,-0.01157359,-0.01143187,-0.01199874,-0.01180978,-0.01417174,-0.01676989,-0.02149381,-0.02565085,-0.02739870,-0.02716250,-0.02409196,-0.02125761,-0.01922633,-0.01813983,-0.01672265,-0.01615578,-0.01421898,-0.01403002,-0.01256561,-0.01105396,-0.00821961,-0.00519630,-0.00325950,-0.00222024,-0.00217300,-0.00155889,0.00014172,0.00269263,0.00529078,0.00666072,0.00680244,0.00562146,0.00396809,0.00236196,0.00155889,0.00037791,0.00089754,0.00127546,0.00297607,0.00538526,0.00751102,0.00798341,0.00713311,0.00505459,0.00387361,0.00410980,0.00510183,0.00571594,0.00429876,0.00151165,-0.00255091,-0.00434600,-0.00538526,-0.00302330,-0.00018896,0.00368465,0.00798341,0.01147911,0.01535272,0.01643922,0.01587235,0.01190426,0.00736931,0.00420428,0.00552698,0.01067604,0.01795087,0.02324165,0.02484779,0.02243859,0.01875394,0.01445518,0.01209322,0.00892820,0.00656624,0.00269263,0.00018896,-0.00203128,-0.00240920,-0.00188957,-0.00321226,-0.00354294,-0.00718035,-0.00944783,-0.01247113,-0.01407726,-0.01393554,-0.01152635,-0.00746378,-0.00118098,0.00453496,0.01095948,0.01450241,0.01828155,0.01875394,0.01837602,0.01440794,0.00940059,0.00283435,0.00033067,0.00028343,0.00562146,0.00958954,0.01185702,0.00902267,0.00415704,-0.00028343,-0.00307054,-0.00373189,-0.00340122,-0.00240920,0.00198404,0.00718035,0.01445518,0.01733676,0.01573063,0.00821961,0.00014172,-0.00656624,-0.00836133,-0.00519630,0.00061411,0.00892820,0.01639198,0.02201344,0.02418644,0.02163552,0.01539996,0.00609385,-0.00349570,-0.01157359,-0.01847050,-0.02149381,-0.02380852,-0.02357233,-0.02121037,-0.01710057,-0.00963678,-0.00108650,0.00751102,0.01521100,0.02007663,0.02291098,0.02347785,0.02187172,0.01818707,0.01379383,0.00755826,0.00377913,0.00004724,-0.00070859,0.00033067,0.00316502,0.00755826,0.01077052,0.01214046,0.00892820,0.00330674,-0.00510183,-0.01289628,-0.02087970,-0.02791833,-0.03448457,-0.03920848,-0.03906676,-0.03443733,-0.02343061,-0.01091224,0.00273987,0.01280181,0.02102142,0.02465883,0.02631220,0.02475331,0.02154105,0.01658094,0.01077052,0.00496011,-0.00061411,-0.00377913,-0.00510183,-0.00373189,-0.00080307,0.00146441,0.00264539,0.00075583,-0.00283435,-0.00694415,-0.01100672,-0.01289628,-0.01464413,-0.01488033,-0.01445518,-0.01266009,-0.01010917,-0.00694415,-0.00444048,-0.00226748,-0.00066135,0.00127546,0.00429876,0.00609385,0.00973126,0.01086500,0.01214046,0.01322696,0.01166807,0.01162083,0.00897544,0.00888096,0.00670796,0.00647176,0.00321226,0.00122822,-0.00188957,-0.00283435,-0.00207852,-0.00061411,0.00222024,0.00325950,0.00340122,0.00212576,-0.00146441,-0.00458220,-0.00821961,-0.01077052,-0.01067604,-0.01043985,-0.00675520,-0.00354294,0.00028343,0.00264539,0.00259815,0.00033067,-0.00273987,-0.00628280,-0.00788894,-0.00869200,-0.00831409,-0.00699139,-0.00552698,-0.00236196,0.00070859,0.00354294,0.00566870,0.00633004,0.00713311,0.00774722,0.00864476,0.01110120,0.01355763,0.01766744,0.02092694,0.02196620,0.02163552,0.01818707,0.01606131,0.01351039,0.01294352,0.01218770,0.01119567,0.01001470,0.00774722,0.00670796,0.00439324,0.00330674,0.00051963,-0.00066135,-0.00259815,-0.00325950,-0.00368465,-0.00354294,-0.00179509,0.00037791,0.00335398,0.00543250,0.00666072,0.00666072,0.00713311,0.00784170,0.01095948,0.01407726,0.01747848,0.01842326,0.01667541,0.01289628,0.00826685,0.00472391,0.00198404,0.00080307,-0.00089754,-0.00179509,-0.00302330,-0.00349570,-0.00302330,-0.00311778,-0.00236196,-0.00203128,-0.00103926,0.00033067,0.00099202,0.00047239,-0.00099202,-0.00439324,-0.00670796,-0.00935335,-0.00888096,-0.00741654,-0.00496011,-0.00330674,-0.00448772,-0.00713311,-0.01043985,-0.01081776,-0.00727483,0.00028343,0.00944783,0.01847050,0.02522570,0.02914655,0.03037476,0.02933550,0.02522570,0.02054902,0.01369935,0.00821961,0.00255091,-0.00174785,-0.00642452,-0.01025089,-0.01483309,-0.01733676,-0.01955700,-0.01851774,-0.01658094,-0.01256561,-0.00902267,-0.00599937,-0.00344846,-0.00160613,0.00113374,0.00344846,0.00618833,0.00779446,0.00954231,0.00954231,0.01001470,0.00911715,0.00869200,0.00821961,0.00859752,0.01006194,0.01138463,0.01251837,0.01237665,0.01129015,0.00921163,0.00746378,0.00510183,0.00373189,0.00151165,-0.00033067,-0.00236196,-0.00292883,-0.00174785,0.00070859,0.00368465,0.00368465,0.00188957,-0.00330674,-0.00760550,-0.01058157,-0.01010917,-0.00571594,-0.00108650,0.00590489,0.00892820,0.01242389,0.01237665,0.01223494,0.01133739,0.01048709,0.00892820,0.00699139,0.00335398,0.00066135,-0.00113374,-0.00136993,0.00151165,0.00311778,0.00656624,0.00746378,0.00774722,0.00774722,0.00552698,0.00477115,0.00188957,-0.00033067,-0.00311778,-0.00481839,-0.00415704,-0.00151165,0.00292883,0.00722759,0.00892820,0.00855028,0.00505459,0.00056687,-0.00477115,-0.01015641,-0.01289628,-0.01360487,-0.00831409,-0.00136993,0.00807789,0.01478585,0.01889565,0.02017111,0.01710057,0.01365211,0.00623557,-0.00004724,-0.00689691,-0.01138463,-0.01421898,-0.01554168,-0.01629750,-0.01653370,-0.01629750,-0.01554168,-0.01450241,-0.01445518,-0.01436070,-0.01431346,-0.01284904,-0.01006194,-0.00628280,-0.00250367,0.00136993,0.00410980,0.00689691,0.00864476,0.01048709,0.01228218,0.01388831,0.01539996,0.01454965,0.01379383,0.01114844,0.00944783,0.00963678,0.00897544,0.00940059,0.00845581,0.00680244,0.00562146,0.00368465,0.00217300,0.00085030,0.00127546,0.00344846,0.00628280,0.00642452,0.00165337,-0.00925887,-0.02234411,-0.03401218,-0.03977535,-0.03883057,-0.03226433,-0.02073798,-0.00614109,0.01162083,0.03042200,0.04605816,0.05697040,0.05909616,0.05356918,0.04275142,0.02683183,0.01228218,-0.00264539,-0.01166807,-0.01639198,-0.01521100,-0.01081776,-0.00784170,-0.00633004,-0.01105396,-0.01724228,-0.02565085,-0.03297292,-0.03741339,-0.03892505,-0.03467353,-0.02560361,-0.01157359,0.00368465,0.01620302,0.02305270,0.02295822,0.01889565,0.01355763,0.01006194,0.00793617,0.00670796,0.00547974,0.00439324,0.00557422,0.00812513,0.01180978,0.01436070,0.01322696,0.00921163,0.00316502,-0.00359017,-0.00703863,-0.01029813,-0.01034537,-0.01171531,-0.01147911,-0.01266009,-0.01129015,-0.00940059,-0.00637728,-0.00264539,-0.00080307,0.00099202,0.00188957,0.00278711,0.00486563,0.00609385,0.00826685,0.00916439,0.00949507,0.00996746,0.00850304,0.00859752,0.00694415,0.00774722,0.00703863,0.00878648,0.00807789,0.00906991,0.00779446,0.00765274,0.00689691,0.00637728,0.00599937,0.00571594,0.00491287,0.00472391,0.00382637,0.00297607,0.00264539,0.00259815,0.00425152,0.00595213,0.00845581,0.00963678,0.01048709,0.01072328,0.01147911,0.01275457,0.01454965,0.01625026,0.01643922,0.01563615,0.01303800,0.00973126,0.00689691,0.00377913,0.00222024,-0.00004724,-0.00127546,-0.00359017,-0.00552698,-0.00821961,-0.01039261,-0.01218770,-0.01228218,-0.01124291,-0.00888096,-0.00699139,-0.00524354,-0.00425152,-0.00269263,-0.00127546,0.00051963,0.00155889,0.00118098,0.00018896,-0.00165337,-0.00255091,-0.00340122,-0.00198404,-0.00089754,0.00207852,0.00467667,0.00689691,0.00817237,0.00741654,0.00609385,0.00396809,0.00207852,0.00099202,-0.00033067,-0.00042515,-0.00132270,-0.00018896,0.00023620,0.00269263,0.00377913,0.00425152,0.00212576,-0.00259815,-0.00883372,-0.01497481,-0.01837602,-0.01643922,-0.01053433,-0.00061411,0.00803065,0.01351039,0.01431346,0.01010917,0.00524354,-0.00023620,-0.00278711,-0.00500735,-0.00614109,-0.00755826,-0.00925887,-0.00977850,-0.01190426,-0.01407726,-0.01870670,-0.02196620,-0.02484779,-0.02333613,-0.02083246,-0.01648646,-0.01190426,-0.00817237,-0.00321226,0.00000000,0.00165337,0.00018896,-0.00382637,-0.00699139,-0.00769998,-0.00448772,0.00118098,0.00722759,0.01152635,0.01403002,0.01492757,0.01492757,0.01440794,0.01384107,0.01185702,0.01029813,0.00727483,0.00425152,0.00103926,-0.00170061,-0.00458220,-0.00666072,-0.00921163,-0.01015641,-0.00944783,-0.00718035,-0.00278711,-0.00056687,0.00179509,0.00051963,0.00023620,-0.00080307,0.00061411,0.00151165,0.00377913,0.00486563,0.00670796,0.00769998,0.00930611,0.00897544,0.00982574,0.00958954,0.01129015,0.01379383,0.01610855,0.01856498,0.01927357,0.01955700,0.01870670,0.01672265,0.01360487,0.00859752,0.00396809,-0.00151165,-0.00387361,-0.00533802,-0.00344846,-0.00212576,0.00018896,0.00023620,0.00089754,0.00094478,0.00193680,0.00236196,0.00363741,0.00231472,0.00448772,0.00519630,0.01058157,0.01431346,0.01837602,0.01823431,0.01658094,0.01176254,0.00623557,0.00004724,-0.00552698,-0.00963678,-0.00973126,-0.00855028,-0.00373189,-0.00042515,0.00316502,0.00529078,0.00779446,0.00935335,0.01110120,0.01029813,0.00911715,0.00680244,0.00481839,0.00325950,0.00278711,0.00240920,0.00373189,0.00481839,0.00623557,0.00670796,0.00661348,0.00628280,0.00661348,0.00684967,0.00713311,0.00604661,0.00496011,0.00486563,0.00524354,0.00661348,0.00529078,0.00264539,-0.00231472,-0.00774722,-0.01053433,-0.01199874,-0.00821961,-0.00382637,0.00255091,0.00680244,0.00850304,0.00779446,0.00505459,0.00349570,0.00240920,0.00321226,0.00401533,0.00571594,0.00784170,0.00982574,0.01218770,0.01166807,0.01010917,0.00666072,0.00292883,0.00141717,0.00212576,0.00557422,0.01152635,0.01634474,0.02040731,0.02111589,0.02045455,0.02012387,0.01922633,0.01672265,0.00982574,-0.00311778,-0.01606131,-0.02593429,-0.02739870,-0.02073798,-0.01091224,-0.00018896,0.00911715,0.01728952,0.02527294,0.03202813,0.03538211,0.03424837,0.02900483,0.02154105,0.01341591,0.00703863,0.00146441,-0.00080307,-0.00203128,-0.00212576,-0.00439324,-0.00982574,-0.01719505,-0.02404472,-0.02787109,-0.02635944,-0.02333613,-0.01752572,-0.01266009,-0.00566870,0.00217300,0.01214046,0.02206068,0.02919379,0.03420113,0.03396494,0.03240605,0.02815452,0.02220239,0.01568339,0.00840857,0.00415704,0.00255091,0.00699139,0.01190426,0.01828155,0.01941528,0.01653370,0.00992022,0.00288159,-0.00269263,-0.00529078,-0.00661348,-0.00514907,-0.00439324,-0.00132270,-0.00028343,0.00146441,0.00122822,0.00051963,-0.00056687,0.00000000,0.00170061,0.00571594,0.01010917,0.01393554,0.01573063,0.01596683,0.01384107,0.01242389,0.01143187,0.01105396,0.01247113,0.01270733,0.01483309,0.01606131,0.01851774,0.01894289,0.01880118,0.01610855,0.01317972,0.01010917,0.00803065,0.00699139,0.00670796,0.00609385,0.00538526,0.00325950,0.00070859,-0.00170061,-0.00359017,-0.00316502,-0.00108650,0.00226748,0.00595213,0.00864476,0.00973126,0.00935335,0.00633004,0.00269263,-0.00132270,-0.00373189,-0.00335398,-0.00113374,0.00170061,0.00415704,0.00392085,0.00193680,-0.00170061,-0.00623557,-0.01001470,-0.01157359,-0.01138463,-0.00807789,-0.00566870,-0.00297607,-0.00387361,-0.00477115,-0.00680244,-0.00779446,-0.00765274,-0.00765274,-0.00684967,-0.00713311,-0.00666072,-0.00703863,-0.00647176,-0.00647176,-0.00510183,-0.00368465,-0.00122822,0.00151165,0.00373189,0.00670796,0.00892820,0.01100672,0.01176254,0.01034537,0.00779446,0.00444048,0.00165337,0.00127546,0.00070859,0.00245644,0.00170061,0.00231472,0.00089754,0.00094478,0.00061411,0.00061411,0.00037791,-0.00070859,-0.00259815,-0.00453496,-0.00694415,-0.00755826,-0.00784170,-0.00633004,-0.00524354,-0.00392085,-0.00316502,-0.00264539,-0.00174785,-0.00203128,-0.00179509,-0.00307054,-0.00392085,-0.00500735,-0.00538526,-0.00552698,-0.00618833,-0.00661348,-0.00774722,-0.00831409,-0.00873924,-0.00873924,-0.00769998,-0.00599937,-0.00288159,0.00014172,0.00269263,0.00377913,0.00292883,0.00174785,-0.00066135,-0.00222024,-0.00458220,-0.00609385,-0.00727483,-0.00746378,-0.00614109,-0.00557422,-0.00392085,-0.00448772,-0.00462944,-0.00529078,-0.00547974,-0.00491287,-0.00420428,-0.00354294,-0.00373189,-0.00406257,-0.00453496,-0.00472391,-0.00354294,-0.00240920,-0.00085030,-0.00023620,0.00014172,-0.00146441,-0.00174785,-0.00368465,-0.00377913,-0.00481839,-0.00533802,-0.00708587,-0.00864476,-0.01067604,-0.01228218,-0.01171531,-0.01147911,-0.00855028,-0.00760550,-0.00618833,-0.00614109,-0.00566870,-0.00529078,-0.00401533,-0.00406257,-0.00425152,-0.00590489,-0.00784170,-0.00949507,-0.01091224,-0.01152635,-0.01129015,-0.01020365,-0.00826685,-0.00618833,-0.00387361,-0.00340122,-0.00283435,-0.00453496,-0.00514907,-0.00566870,-0.00420428,-0.00231472,-0.00056687,0.00066135,-0.00051963,-0.00094478,-0.00217300,-0.00207852,-0.00118098,-0.00151165,-0.00122822,-0.00283435,-0.00340122,-0.00538526,-0.00656624,-0.00784170,-0.00850304,-0.00651900,-0.00453496,-0.00085030,0.00099202,0.00160613,0.00165337,0.00047239,0.00028343,-0.00113374,-0.00207852,-0.00373189,-0.00420428,-0.00420428,-0.00359017,-0.00368465,-0.00529078,-0.00774722,-0.01199874,-0.01521100,-0.02012387,-0.02253307,-0.02565085,-0.02461159,-0.02253307,-0.01691161,-0.01129015,-0.00467667,0.00085030,0.00557422,0.00826685,0.00859752,0.00656624,0.00132270,-0.00377913,-0.01086500,-0.01516376,-0.02121037,-0.02451711,-0.02815452,-0.02876863,-0.02711526,-0.02239135,-0.01539996,-0.00826685,-0.00217300,-0.00018896,-0.00127546,-0.00547974,-0.01105396,-0.01426622,-0.01606131,-0.01360487,-0.00921163,-0.00396809,0.00259815,0.00618833,0.00930611,0.00826685,0.00566870,0.00028343,-0.00562146,-0.01129015,-0.01530548,-0.01757296,-0.01728952,-0.01625026,-0.01421898,-0.01284904,-0.01162083,-0.01157359,-0.01025089,-0.01015641,-0.00840857,-0.00779446,-0.00585765,-0.00533802,-0.00340122,-0.00382637,-0.00240920,-0.00264539,-0.00094478,0.00051963,0.00278711,0.00458220,0.00599937,0.00623557,0.00562146,0.00302330,-0.00047239,-0.00595213,-0.00982574,-0.01374659,-0.01469137,-0.01473861,-0.01521100,-0.01530548,-0.01733676,-0.01950976,-0.02139933,-0.02309994,-0.02239135,-0.02007663,-0.01530548,-0.00963678,-0.00467667,-0.00070859,0.00075583,0.00184233,0.00122822,0.00132270,0.00099202,0.00070859,0.00122822,0.00122822,0.00184233,0.00089754,-0.00066135,-0.00354294,-0.00529078,-0.00732207,-0.00736931,-0.00793617,-0.00751102,-0.00751102,-0.00571594,-0.00425152,-0.00170061,-0.00103926,-0.00118098,-0.00302330,-0.00481839,-0.00633004,-0.00722759,-0.00788894,-0.00845581,-0.00831409,-0.00713311,-0.00415704,0.00009448,0.00458220,0.00873924,0.01043985,0.01058157,0.00736931,0.00330674,-0.00222024,-0.00694415,-0.01039261,-0.01199874,-0.01138463,-0.01062881,-0.00859752,-0.00845581,-0.00718035,-0.00727483,-0.00633004,-0.00505459,-0.00325950,-0.00155889,0.00009448,0.00051963,0.00085030,0.00014172,-0.00094478,-0.00155889,-0.00250367,-0.00231472,-0.00094478,0.00014172,0.00231472,0.00245644,0.00184233,0.00000000,-0.00264539,-0.00448772,-0.00552698,-0.00552698,-0.00425152,-0.00321226,-0.00283435,-0.00382637,-0.00694415,-0.01114844,-0.01610855,-0.02021835,-0.02295822,-0.02243859,-0.01903737,-0.01280181,-0.00335398,0.00571594,0.01511652,0.02026559,0.02338337,0.02154105,0.01880118,0.01351039,0.00973126,0.00590489,0.00538526,0.00566870,0.00888096,0.01072328,0.01199874,0.00949507,0.00505459,-0.00075583,-0.00557422,-0.00751102,-0.00826685,-0.00703863,-0.00741654,-0.00798341,-0.00992022,-0.01105396,-0.01176254,-0.01081776,-0.00958954,-0.00703863,-0.00297607,0.00151165,0.00769998,0.01190426,0.01426622,0.01469137,0.01171531,0.00855028,0.00439324,0.00174785,-0.00037791,-0.00033067,-0.00028343,0.00094478,0.00136993,0.00184233,0.00103926,0.00051963,-0.00094478,-0.00226748,-0.00477115,-0.00732207,-0.01077052,-0.01336868,-0.01573063,-0.01558891,-0.01459689,-0.01043985,-0.00670796,-0.00132270,0.00226748,0.00543250,0.00694415,0.00765274,0.00718035,0.00538526,0.00292883,-0.00056687,-0.00359017,-0.00543250,-0.00661348,-0.00604661,-0.00477115,-0.00316502,-0.00080307,0.00122822,0.00288159,0.00401533,0.00396809,0.00226748,-0.00037791,-0.00467667,-0.00916439,-0.01237665,-0.01445518,-0.01275457,-0.00973126,-0.00500735,-0.00080307,0.00141717,0.00160613,0.00056687,-0.00103926,-0.00118098,-0.00174785,-0.00094478,-0.00203128,-0.00359017,-0.00505459,-0.00680244,-0.00623557,-0.00609385,-0.00510183,-0.00656624,-0.00769998,-0.01058157,-0.01209322,-0.01289628,-0.01289628,-0.01138463,-0.01039261,-0.00897544,-0.00921163,-0.00930611,-0.01010917,-0.00930611,-0.00855028,-0.00694415,-0.00656624,-0.00642452,-0.00755826,-0.00732207,-0.00689691,-0.00481839,-0.00302330,-0.00160613,-0.00174785,-0.00240920,-0.00321226,-0.00392085,-0.00302330,-0.00349570,-0.00255091,-0.00387361,-0.00439324,-0.00581041,-0.00689691,-0.00675520,-0.00788894,-0.00689691,-0.00699139,-0.00623557,-0.00604661,-0.00680244,-0.00736931,-0.00845581,-0.00831409,-0.00812513,-0.00732207,-0.00699139,-0.00741654,-0.00769998,-0.00892820,-0.01039261,-0.01256561,-0.01530548,-0.01695885,-0.01780915,-0.01634474,-0.01417174,-0.01176254,-0.00940059,-0.00840857,-0.00718035,-0.00647176,-0.00590489,-0.00571594,-0.00562146,-0.00661348,-0.00642452,-0.00736931,-0.00732207,-0.00831409,-0.01006194,-0.01223494,-0.01535272,-0.01620302,-0.01653370,-0.01388831,-0.01039261,-0.00746378,-0.00505459,-0.00434600,-0.00453496,-0.00477115,-0.00571594,-0.00684967,-0.00878648,-0.01091224,-0.01289628,-0.01398278,-0.01365211,-0.01256561,-0.01034537,-0.00793617,-0.00533802,-0.00349570,-0.00217300,-0.00207852,-0.00236196,-0.00311778,-0.00335398,-0.00255091,-0.00070859,0.00302330,0.00609385,0.00888096,0.00944783,0.00803065,0.00633004,0.00429876,0.00387361,0.00472391,0.00557422,0.00718035,0.00736931,0.00803065,0.00736931,0.00713311,0.00524354,0.00363741,0.00066135,-0.00080307,-0.00226748,-0.00094478,0.00018896,0.00288159,0.00392085,0.00552698,0.00585765,0.00694415,0.00793617,0.00765274,0.00684967,0.00297607,-0.00009448,-0.00382637,-0.00533802,-0.00500735,-0.00462944,-0.00292883,-0.00203128,-0.00103926,0.00023620,0.00118098,0.00184233,0.00231472,0.00283435,0.00382637,0.00557422,0.00670796,0.00760550,0.00614109,0.00486563,0.00165337,0.00028343,-0.00070859,0.00023620,0.00330674,0.00680244,0.01209322,0.01573063,0.01894289,0.01903737,0.01738400,0.01346315,0.00940059,0.00467667,0.00198404,-0.00075583,-0.00127546,-0.00188957,-0.00127546,-0.00014172,0.00132270,0.00368465,0.00500735,0.00675520,0.00633004,0.00599937,0.00410980,0.00330674,0.00170061,0.00179509,0.00160613,0.00245644,0.00420428,0.00581041,0.00713311,0.00746378,0.00576317,0.00368465,0.00094478,-0.00061411,-0.00118098,0.00023620,0.00193680,0.00453496,0.00604661,0.00675520,0.00614109,0.00500735,0.00359017,0.00269263,0.00155889,0.00061411,-0.00023620,-0.00014172,0.00061411,0.00283435,0.00467667,0.00585765,0.00713311,0.00618833,0.00599937,0.00373189,0.00165337,-0.00127546,-0.00302330,-0.00448772,-0.00401533,-0.00359017,-0.00368465,-0.00401533,-0.00581041,-0.00670796,-0.00774722,-0.00779446,-0.00746378,-0.00651900,-0.00519630,-0.00377913,-0.00170061,0.00037791,0.00222024,0.00406257,0.00458220,0.00401533,0.00245644,0.00028343,-0.00207852,-0.00288159,-0.00377913,-0.00222024,-0.00094478,0.00231472,0.00477115,0.00765274,0.00840857,0.00826685,0.00647176,0.00373189,0.00122822,-0.00198404,-0.00387361,-0.00543250,-0.00633004,-0.00562146,-0.00510183,-0.00325950,-0.00136993,0.00028343,0.00179509,0.00231472,0.00103926,-0.00018896,-0.00335398,-0.00562146,-0.00736931,-0.00831409,-0.00817237,-0.00765274,-0.00741654,-0.00666072,-0.00689691,-0.00552698,-0.00514907,-0.00288159,-0.00122822,0.00051963,0.00174785,0.00273987,0.00245644,0.00250367,0.00170061,0.00094478,-0.00070859,-0.00132270,-0.00250367,-0.00108650,0.00051963,0.00269263,0.00359017,0.00278711,0.00014172,-0.00160613,-0.00425152,-0.00377913,-0.00496011,-0.00514907,-0.00562146,-0.00708587,-0.00642452,-0.00670796,-0.00486563,-0.00392085,-0.00297607,-0.00292883,-0.00434600,-0.00552698,-0.00826685,-0.00883372,-0.00968402,-0.00831409,-0.00699139,-0.00590489,-0.00392085,-0.00392085,-0.00203128,-0.00188957,-0.00061411,0.00018896,0.00009448,0.00023620,-0.00118098,-0.00288159,-0.00434600,-0.00599937,-0.00590489,-0.00524354,-0.00340122,-0.00165337,0.00037791,0.00127546,0.00250367,0.00217300,0.00207852,0.00056687,-0.00075583,-0.00217300,-0.00316502,-0.00415704,-0.00401533,-0.00368465,-0.00245644,-0.00198404,-0.00160613,-0.00231472,-0.00297607,-0.00278711,-0.00250367,-0.00099202,-0.00151165,-0.00207852,-0.00462944,-0.00694415,-0.00788894,-0.00803065,-0.00562146,-0.00340122,-0.00122822,0.00009448,-0.00023620,-0.00108650,-0.00236196,-0.00325950,-0.00207852,-0.00023620,0.00283435,0.00581041,0.00718035,0.00784170,0.00633004,0.00472391,0.00231472,0.00047239,-0.00231472,-0.00472391,-0.00831409,-0.01062881,-0.01228218,-0.01261285,-0.01114844,-0.01129015,-0.01043985,-0.01143187,-0.01162083,-0.01124291,-0.01006194,-0.00826685,-0.00590489,-0.00307054,-0.00056687,0.00297607,0.00467667,0.00585765,0.00500735,0.00349570,0.00240920,0.00278711,0.00486563,0.00755826,0.01015641,0.01072328,0.01129015,0.00911715,0.00845581,0.00543250,0.00434600,0.00245644,0.00155889,0.00193680,0.00179509,0.00278711,0.00226748,0.00174785,0.00089754,0.00056687,0.00127546,0.00273987,0.00538526,0.00732207,0.00892820,0.00888096,0.00699139,0.00524354,0.00255091,0.00236196,0.00151165,0.00335398,0.00316502,0.00462944,0.00444048,0.00453496,0.00514907,0.00524354,0.00581041,0.00618833,0.00434600,0.00207852,-0.00236196,-0.00614109,-0.00930611,-0.00958954,-0.00850304,-0.00496011,-0.00174785,0.00127546,0.00302330,0.00292883,0.00269263,0.00094478,0.00170061,0.00269263,0.00547974,0.00826685,0.01006194,0.01081776,0.01077052,0.01029813,0.01015641,0.01029813,0.01029813,0.01029813,0.01067604,0.01053433,0.01077052,0.01034537,0.00911715,0.00836133,0.00557422,0.00368465,0.00089754,-0.00033067,-0.00056687,0.00070859,0.00188957,0.00240920,0.00179509,-0.00033067,-0.00231472,-0.00368465,-0.00462944,-0.00396809,-0.00349570,-0.00231472,-0.00037791,0.00188957,0.00420428,0.00585765,0.00628280,0.00628280,0.00614109,0.00637728,0.00760550,0.00755826,0.00807789,0.00562146,0.00415704,0.00165337,0.00207852,0.00273987,0.00533802,0.00727483,0.00883372,0.01006194,0.01043985,0.01129015,0.01143187,0.01095948,0.00996746,0.00873924,0.00836133,0.00850304,0.00944783,0.00973126,0.01006194,0.00821961,0.00699139,0.00425152,0.00354294,0.00250367,0.00302330,0.00316502,0.00396809,0.00434600,0.00505459,0.00557422,0.00599937,0.00590489,0.00519630,0.00420428,0.00273987,0.00255091,0.00236196,0.00340122,0.00444048,0.00472391,0.00453496,0.00321226,0.00141717,0.00047239,-0.00070859,0.00018896,0.00085030,0.00217300,0.00307054,0.00387361,0.00335398,0.00359017,0.00212576,0.00170061,0.00113374,0.00146441,0.00174785,0.00292883,0.00288159,0.00288159,0.00184233,0.00042515,-0.00103926,-0.00236196,-0.00292883,-0.00288159,-0.00160613,-0.00028343,0.00179509,0.00340122,0.00453496,0.00486563,0.00425152,0.00283435,0.00174785,0.00033067,0.00080307,0.00099202,0.00222024,0.00302330,0.00373189,0.00439324,0.00552698,0.00633004,0.00755826,0.00798341,0.00769998,0.00713311,0.00566870,0.00429876,0.00231472,0.00118098,-0.00018896,0.00089754,0.00170061,0.00486563,0.00718035,0.01015641,0.01195150,0.01275457,0.01270733,0.01204598,0.01119567,0.01058157,0.01006194,0.00921163,0.00902267,0.00751102,0.00812513,0.00694415,0.00812513,0.00751102,0.00798341,0.00746378,0.00836133,0.00850304,0.00987298,0.01010917,0.01025089,0.00902267,0.00732207,0.00410980,0.00103926,-0.00212576,-0.00377913,-0.00311778,-0.00066135,0.00316502,0.00708587,0.00921163,0.01152635,0.01110120,0.01195150,0.01162083,0.01147911,0.01199874,0.01176254,0.01242389,0.01299076,0.01313248,0.01384107,0.01284904,0.01275457,0.01129015,0.01086500,0.01020365,0.00954231,0.00977850,0.00840857,0.00831409,0.00666072,0.00656624,0.00647176,0.00774722,0.00850304,0.00883372,0.00850304,0.00656624,0.00633004,0.00439324,0.00505459,0.00401533,0.00410980,0.00392085,0.00444048,0.00618833,0.00878648,0.01105396,0.01299076,0.01355763,0.01351039,0.01289628,0.01251837,0.01058157,0.00977850,0.00684967,0.00566870,0.00439324,0.00434600,0.00472391,0.00543250,0.00590489,0.00486563,0.00448772,0.00188957,0.00056687,-0.00037791,-0.00047239,0.00198404,0.00377913,0.00666072,0.00741654,0.00755826,0.00642452,0.00462944,0.00382637,0.00269263,0.00340122,0.00340122,0.00377913,0.00321226,0.00122822,-0.00103926,-0.00354294,-0.00566870,-0.00647176,-0.00680244,-0.00618833,-0.00453496,-0.00269263,-0.00004724,0.00259815,0.00467667,0.00651900,0.00727483,0.00760550,0.00765274,0.00666072,0.00519630,0.00292883,0.00061411,-0.00094478,-0.00198404,-0.00179509,-0.00160613,-0.00099202,-0.00023620,-0.00018896,0.00075583,0.00009448,0.00051963,-0.00075583,-0.00028343,-0.00033067,0.00056687,0.00184233,0.00193680,0.00259815,0.00198404,0.00231472,0.00222024,0.00269263,0.00207852,0.00099202,-0.00047239,-0.00160613,-0.00245644,-0.00132270,-0.00132270,0.00033067,0.00028343,0.00028343,0.00009448,-0.00127546,-0.00245644,-0.00453496,-0.00604661,-0.00784170,-0.00784170,-0.00878648,-0.00703863,-0.00633004,-0.00453496,-0.00316502,-0.00217300,-0.00136993,-0.00023620,-0.00023620,0.00051963,-0.00103926,-0.00222024,-0.00444048,-0.00486563,-0.00377913,-0.00141717,0.00136993,0.00363741,0.00462944,0.00420428,0.00255091,-0.00037791,-0.00349570,-0.00614109,-0.00732207,-0.00666072,-0.00472391,-0.00170061,0.00004724,0.00127546,0.00099202,0.00023620,0.00014172,0.00061411,0.00151165,0.00269263,0.00222024,0.00231472,0.00122822,0.00118098,0.00122822,0.00094478,0.00127546,0.00037791,0.00080307,0.00061411,0.00160613,0.00255091,0.00335398,0.00453496,0.00420428,0.00415704,0.00217300,0.00127546,-0.00047239,0.00047239,0.00118098,0.00330674,0.00453496,0.00543250,0.00496011,0.00458220,0.00387361,0.00170061,0.00042515,-0.00278711,-0.00496011,-0.00661348,-0.00703863,-0.00514907,-0.00193680,0.00255091,0.00666072,0.01034537,0.01100672,0.01081776,0.00736931,0.00406257,-0.00018896,-0.00288159,-0.00453496,-0.00410980,-0.00217300,0.00014172,0.00344846,0.00533802,0.00642452,0.00595213,0.00434600,0.00212576,0.00033067,-0.00080307,-0.00033067,0.00051963,0.00297607,0.00420428,0.00566870,0.00547974,0.00392085,0.00240920,-0.00089754,-0.00212576,-0.00368465,-0.00368465,-0.00292883,-0.00212576,-0.00080307,-0.00018896,0.00018896,-0.00047239,-0.00188957,-0.00373189,-0.00628280,-0.00689691,-0.00864476,-0.00718035,-0.00713311,-0.00571594,-0.00472391,-0.00448772,-0.00420428,-0.00496011,-0.00571594,-0.00675520,-0.00798341,-0.00873924,-0.00968402,-0.01006194,-0.01015641,-0.01001470,-0.00987298,-0.00888096,-0.00727483,-0.00462944,-0.00108650,0.00127546,0.00363741,0.00297607,0.00325950,0.00259815,0.00288159,0.00330674,0.00203128,0.00004724,-0.00415704,-0.00836133,-0.01251837,-0.01539996,-0.01601407,-0.01464413,-0.01129015,-0.00684967,-0.00297607,-0.00103926,-0.00023620,-0.00151165,-0.00222024,-0.00377913,-0.00363741,-0.00519630,-0.00547974,-0.00836133,-0.00944783,-0.01162083,-0.00982574,-0.00812513,-0.00288159,0.00042515,0.00325950,0.00307054,0.00188957,-0.00023620,-0.00174785,-0.00250367,-0.00255091,-0.00231472,-0.00132270,-0.00108650,0.00014172,0.00023620,0.00009448,-0.00028343,-0.00231472,-0.00354294,-0.00637728,-0.00680244,-0.00826685,-0.00699139,-0.00694415,-0.00514907,-0.00472391,-0.00382637,-0.00316502,-0.00316502,-0.00269263,-0.00349570,-0.00344846,-0.00359017,-0.00259815,-0.00103926,0.00080307,0.00245644,0.00354294,0.00302330,0.00236196,0.00047239,-0.00127546,-0.00302330,-0.00472391,-0.00618833,-0.00788894,-0.00982574,-0.01110120,-0.01199874,-0.01091224,-0.00992022,-0.00779446,-0.00722759,-0.00628280,-0.00647176,-0.00547974,-0.00425152,-0.00203128,0.00004724,0.00103926,0.00146441,0.00037791,-0.00094478,-0.00236196,-0.00368465,-0.00439324,-0.00458220,-0.00481839,-0.00368465,-0.00321226,-0.00170061,-0.00080307,-0.00009448,0.00033067,-0.00075583,-0.00155889,-0.00406257,-0.00500735,-0.00566870,-0.00481839,-0.00278711,-0.00014172,0.00283435,0.00491287,0.00680244,0.00666072,0.00675520,0.00543250,0.00448772,0.00288159,0.00203128,0.00042515,0.00028343,-0.00085030,-0.00066135,-0.00193680,-0.00269263,-0.00519630,-0.00581041,-0.00713311,-0.00552698,-0.00396809,-0.00127546,0.00122822,0.00311778,0.00510183,0.00637728,0.00708587,0.00708587,0.00637728,0.00562146,0.00581041,0.00637728,0.00812513,0.00987298,0.01166807,0.01256561,0.01284904,0.01114844,0.00850304,0.00505459,0.00113374,-0.00179509,-0.00373189,-0.00514907,-0.00410980,-0.00340122,-0.00184233,-0.00037791,-0.00037791,0.00009448,-0.00042515,-0.00070859,-0.00070859,-0.00198404,-0.00288159,-0.00382637,-0.00458220,-0.00264539,-0.00179509,0.00023620,-0.00037791,-0.00089754,-0.00292883,-0.00410980,-0.00472391,-0.00500735,-0.00415704,-0.00264539,-0.00023620,0.00240920,0.00462944,0.00576317,0.00547974,0.00477115,0.00359017,0.00226748,0.00170061,0.00042515,-0.00028343,-0.00080307,-0.00127546,-0.00188957,-0.00245644,-0.00344846,-0.00344846,-0.00311778,-0.00198404,-0.00212576,-0.00255091,-0.00462944,-0.00581041,-0.00614109,-0.00496011,-0.00316502,-0.00179509,-0.00122822,-0.00255091,-0.00335398,-0.00519630,-0.00510183,-0.00439324,-0.00222024,0.00075583,0.00311778,0.00533802,0.00453496,0.00505459,0.00255091,0.00222024,0.00033067,-0.00023620,-0.00075583,0.00075583,0.00226748,0.00514907,0.00618833,0.00680244,0.00444048,0.00278711,-0.00042515,-0.00160613,-0.00307054,-0.00259815,-0.00240920,-0.00042515,0.00033067,0.00193680,0.00146441,0.00151165,-0.00033067,-0.00217300,-0.00307054,-0.00439324,-0.00307054,-0.00165337,0.00018896,0.00217300,0.00226748,0.00141717,-0.00056687,-0.00302330,-0.00467667,-0.00562146,-0.00458220,-0.00264539,0.00028343,0.00278711,0.00496011,0.00547974,0.00571594,0.00458220,0.00269263,0.00037791,-0.00264539,-0.00514907,-0.00826685,-0.01053433,-0.01336868,-0.01393554,-0.01421898,-0.01105396,-0.00788894,-0.00349570,0.00028343,0.00165337,0.00278711,0.00226748,0.00070859,0.00080307,-0.00108650,0.00018896,0.00000000,0.00089754,0.00080307,0.00070859,-0.00018896,0.00023620,0.00018896,0.00033067,0.00023620,-0.00170061,-0.00415704,-0.00722759,-0.01020365,-0.01077052,-0.00963678,-0.00547974,-0.00108650,0.00321226,0.00467667,0.00453496,0.00340122,0.00236196,0.00207852,0.00151165,0.00042515,-0.00061411,-0.00203128,-0.00136993,-0.00132270,0.00009448,-0.00075583,-0.00170061,-0.00453496,-0.00628280,-0.00718035,-0.00642452,-0.00325950,-0.00051963,0.00212576,0.00222024,0.00056687,-0.00127546,-0.00203128,-0.00033067,0.00302330,0.00708587,0.01043985,0.01294352,0.01393554,0.01384107,0.01124291,0.00741654,0.00122822,-0.00307054,-0.00769998,-0.00812513,-0.00892820,-0.00751102,-0.00684967,-0.00628280,-0.00576317,-0.00604661,-0.00637728,-0.00684967,-0.00642452,-0.00462944,-0.00203128,0.00203128,0.00467667,0.00736931,0.00812513,0.00850304,0.00793617,0.00722759,0.00651900,0.00604661,0.00595213,0.00557422,0.00519630,0.00429876,0.00363741,0.00330674,0.00340122,0.00434600,0.00514907,0.00547974,0.00472391,0.00273987,0.00009448,-0.00273987,-0.00458220,-0.00514907,-0.00420428,-0.00264539,-0.00080307,0.00000000,0.00009448,0.00000000,-0.00009448,0.00080307,0.00170061,0.00264539,0.00198404,0.00136993,-0.00066135,-0.00155889,-0.00207852,-0.00103926,0.00113374,0.00396809,0.00628280,0.00807789,0.00736931,0.00628280,0.00420428,0.00259815,0.00217300,0.00188957,0.00160613,0.00099202,-0.00014172,-0.00132270,-0.00174785,-0.00184233,-0.00103926,-0.00014172,0.00132270,0.00226748,0.00307054,0.00273987,0.00179509,0.00066135,-0.00014172,0.00056687,0.00080307,0.00231472,0.00170061,0.00127546,0.00014172,-0.00051963,0.00014172,0.00127546,0.00311778,0.00444048,0.00585765,0.00618833,0.00642452,0.00581041,0.00453496,0.00297607,0.00056687,-0.00089754,-0.00217300,-0.00231472,-0.00122822,-0.00018896,0.00188957,0.00273987,0.00325950,0.00307054,0.00269263,0.00264539,0.00259815,0.00245644,0.00179509,0.00085030,-0.00023620,-0.00099202,-0.00056687,-0.00009448,0.00184233,0.00193680,0.00236196,-0.00004724,-0.00273987,-0.00651900,-0.00944783,-0.01067604,-0.01043985,-0.00793617,-0.00467667,-0.00070859,0.00330674,0.00633004,0.00755826,0.00779446,0.00680244,0.00562146,0.00571594,0.00500735,0.00491287,0.00321226,0.00113374,-0.00099202,-0.00245644,-0.00297607,-0.00292883,-0.00236196,-0.00231472,-0.00165337,-0.00193680,-0.00141717,-0.00170061,-0.00151165,-0.00136993,-0.00085030,0.00000000,0.00070859,0.00132270,0.00122822,0.00122822,0.00075583,0.00099202,0.00136993,0.00174785,0.00155889,0.00042515,-0.00118098,-0.00288159,-0.00344846,-0.00316502,-0.00212576,-0.00047239,0.00066135,0.00174785,0.00264539,0.00255091,0.00259815,0.00188957,0.00141717,0.00108650,0.00122822,0.00160613,0.00155889,0.00094478,-0.00028343,-0.00132270,-0.00198404,-0.00174785,-0.00222024,-0.00212576,-0.00273987,-0.00354294,-0.00288159,-0.00359017,-0.00198404,-0.00170061,-0.00047239,0.00103926,0.00198404,0.00311778,0.00292883,0.00165337,0.00004724,-0.00141717,-0.00316502,-0.00349570,-0.00496011,-0.00557422,-0.00529078,-0.00359017,-0.00056687,0.00349570,0.00694415,0.00954231,0.01157359,0.01270733,0.01280181,0.01266009,0.01086500,0.01062881,0.00940059,0.00973126,0.00855028,0.00793617,0.00637728,0.00557422,0.00500735,0.00354294,0.00170061,-0.00231472,-0.00429876,-0.00576317,-0.00444048,-0.00359017,-0.00325950,-0.00462944,-0.00637728,-0.00684967,-0.00666072,-0.00496011,-0.00344846,-0.00174785,0.00028343,0.00273987,0.00500735,0.00599937,0.00628280,0.00491287,0.00382637,0.00255091,0.00118098,0.00009448,-0.00155889,-0.00193680,-0.00217300,-0.00132270,-0.00033067,0.00056687,0.00165337,0.00250367,0.00302330,0.00184233,-0.00075583,-0.00472391,-0.00911715,-0.01176254,-0.01351039,-0.01270733,-0.01209322,-0.01129015,-0.01195150,-0.01242389,-0.01232941,-0.00992022,-0.00571594,-0.00033067,0.00462944,0.00769998,0.00930611,0.00925887,0.00850304,0.00765274,0.00708587,0.00656624,0.00614109,0.00462944,0.00273987,0.00033067,-0.00056687,-0.00051963,0.00118098,0.00292883,0.00373189,0.00382637,0.00330674,0.00288159,0.00240920,0.00174785,0.00018896,-0.00151165,-0.00217300,-0.00240920,-0.00099202,-0.00018896,0.00056687,-0.00004724,-0.00042515,-0.00198404,-0.00108650,0.00033067,0.00392085,0.00755826,0.01010917,0.00982574,0.00769998,0.00363741,0.00103926,-0.00165337,-0.00269263,-0.00453496,-0.00557422,-0.00609385,-0.00656624,-0.00590489,-0.00684967,-0.00760550,-0.00788894,-0.00769998,-0.00590489,-0.00425152,-0.00316502,-0.00118098,0.00014172,0.00401533,0.00680244,0.00897544,0.00930611,0.00765274,0.00609385,0.00467667,0.00425152,0.00425152,0.00481839,0.00533802,0.00618833,0.00566870,0.00410980,0.00089754,-0.00311778,-0.00651900,-0.00902267,-0.01001470,-0.00916439,-0.00684967,-0.00217300,0.00311778,0.00873924,0.01308524,0.01388831,0.01332144,0.00897544,0.00448772,-0.00070859,-0.00552698,-0.00836133,-0.01020365,-0.01072328,-0.01039261,-0.00973126,-0.00873924,-0.00689691,-0.00444048,-0.00042515,0.00340122,0.00746378,0.00982574,0.01072328,0.01010917,0.00859752,0.00642452,0.00477115,0.00259815,0.00089754,0.00009448,-0.00023620,0.00136993,0.00316502,0.00496011,0.00618833,0.00628280,0.00614109,0.00642452,0.00699139,0.00751102,0.00675520,0.00519630,0.00269263,0.00085030,0.00014172,0.00023620,0.00151165,0.00292883,0.00439324,0.00524354,0.00633004,0.00477115,0.00335398,-0.00051963,-0.00392085,-0.00647176,-0.00803065,-0.00746378,-0.00651900,-0.00486563,-0.00307054,-0.00113374,0.00151165,0.00429876,0.00670796,0.00774722,0.00713311,0.00477115,0.00222024,-0.00028343,-0.00080307,-0.00051963,0.00099202,0.00212576,0.00377913,0.00462944,0.00666072,0.00765274,0.00812513,0.00675520,0.00363741,0.00070859,-0.00207852,-0.00207852,-0.00155889,0.00033067,0.00132270,0.00174785,0.00122822,0.00070859,-0.00018896,-0.00047239,-0.00108650,-0.00132270,-0.00160613,-0.00170061,-0.00184233,-0.00136993,-0.00070859,0.00222024,0.00401533,0.00755826,0.00840857,0.00897544,0.00793617,0.00552698,0.00255091,-0.00004724,-0.00236196,-0.00245644,-0.00099202,0.00061411,0.00222024,0.00132270,-0.00103926,-0.00340122,-0.00566870,-0.00614109,-0.00633004,-0.00642452,-0.00684967,-0.00684967,-0.00576317,-0.00302330,0.00094478,0.00543250,0.00845581,0.01077052,0.00973126,0.00840857,0.00571594,0.00316502,0.00141717,0.00014172,0.00004724,0.00085030,0.00335398,0.00581041,0.00864476,0.00878648,0.00670796,0.00245644,-0.00321226,-0.00661348,-0.00850304,-0.00751102,-0.00496011,-0.00245644,-0.00023620,0.00113374,0.00033067,-0.00033067,-0.00255091,-0.00344846,-0.00382637,-0.00302330,-0.00236196,-0.00193680,-0.00269263,-0.00316502,-0.00373189,-0.00330674,-0.00264539,-0.00188957,-0.00136993,-0.00160613,-0.00170061,-0.00203128,-0.00198404,-0.00127546,-0.00018896,0.00070859,0.00146441,0.00056687,-0.00113374,-0.00316502,-0.00500735,-0.00614109,-0.00562146,-0.00505459,-0.00359017,-0.00269263,-0.00217300,-0.00174785,-0.00160613,-0.00037791,0.00000000,0.00132270,0.00075583,0.00000000,-0.00151165,-0.00264539,-0.00373189,-0.00410980,-0.00472391,-0.00519630,-0.00491287,-0.00514907,-0.00472391,-0.00514907,-0.00538526,-0.00458220,-0.00302330,0.00018896,0.00340122,0.00543250,0.00689691,0.00505459,0.00349570,-0.00174785,-0.00496011,-0.00925887,-0.01029813,-0.00906991,-0.00656624,-0.00297607,-0.00136993,-0.00014172,-0.00033067,0.00061411,0.00051963,0.00099202,-0.00004724,-0.00118098,-0.00222024,-0.00335398,-0.00344846,-0.00434600,-0.00410980,-0.00439324,-0.00354294,-0.00264539,-0.00136993,-0.00018896,0.00037791,0.00018896,-0.00108650,-0.00264539,-0.00439324,-0.00477115,-0.00382637,-0.00236196,-0.00042515,0.00000000,0.00018896,-0.00014172,0.00004724,-0.00042515,-0.00061411,-0.00146441,-0.00207852,-0.00212576,-0.00217300,-0.00207852,-0.00207852,-0.00283435,-0.00429876,-0.00722759,-0.01020365,-0.01289628,-0.01322696,-0.01001470,-0.00585765,-0.00061411,0.00174785,0.00141717,0.00023620,-0.00226748,-0.00344846,-0.00448772,-0.00496011,-0.00472391,-0.00429876,-0.00439324,-0.00614109,-0.00916439,-0.01242389,-0.01299076,-0.00954231,-0.00269263,0.00396809,0.00878648,0.00821961,0.00595213,0.00269263,0.00051963,0.00132270,0.00165337,0.00259815,0.00141717,-0.00103926,-0.00434600,-0.00699139,-0.00821961,-0.00727483,-0.00576317,-0.00368465,-0.00222024,-0.00160613,-0.00099202,-0.00141717,-0.00122822,-0.00203128,-0.00273987,-0.00510183,-0.00779446,-0.01204598,-0.01568339,-0.01804535,-0.01790363,-0.01473861,-0.00855028,-0.00217300,0.00533802,0.01039261,0.01393554,0.01563615,0.01384107,0.01157359,0.00689691,0.00222024,-0.00259815,-0.00817237,-0.01308524,-0.01672265,-0.01875394,-0.01563615,-0.01114844,-0.00335398,0.00165337,0.00519630,0.00321226,0.00061411,-0.00439324,-0.00699139,-0.00836133,-0.00864476,-0.00821961,-0.00831409,-0.00892820,-0.00859752,-0.00850304,-0.00779446,-0.00656624,-0.00581041,-0.00349570,-0.00179509,0.00127546,0.00240920,0.00344846,0.00250367,0.00203128,0.00122822,0.00151165,0.00188957,0.00217300,0.00292883,0.00363741,0.00439324,0.00595213,0.00670796,0.00812513,0.00935335,0.01034537,0.01157359,0.01180978,0.01095948,0.01095948,0.00930611,0.00944783,0.00793617,0.00699139,0.00510183,0.00373189,0.00236196,0.00222024,0.00231472,0.00292883,0.00330674,0.00311778,0.00283435,0.00198404,0.00146441,0.00037791,-0.00051963,-0.00231472,-0.00392085,-0.00538526,-0.00680244,-0.00694415,-0.00718035,-0.00595213,-0.00524354,-0.00259815,-0.00051963,0.00288159,0.00514907,0.00637728,0.00623557,0.00562146,0.00420428,0.00368465,0.00240920,0.00061411,-0.00099202,-0.00396809,-0.00566870,-0.00807789,-0.00897544,-0.01077052,-0.00996746,-0.01077052,-0.00803065,-0.00755826,-0.00614109,-0.00718035,-0.00897544,-0.01133739,-0.01166807,-0.01119567,-0.00845581,-0.00590489,-0.00292883,0.00033067,0.00321226,0.00684967,0.00869200,0.00902267,0.00708587,0.00354294,0.00000000,-0.00184233,-0.00255091,-0.00099202,0.00042515,0.00184233,0.00108650,-0.00056687,-0.00340122,-0.00604661,-0.00746378,-0.00869200,-0.00845581,-0.00916439,-0.00845581,-0.00902267,-0.00774722,-0.00779446,-0.00684967,-0.00751102,-0.00746378,-0.00836133,-0.00869200,-0.00902267,-0.00982574,-0.01006194,-0.01034537,-0.00845581,-0.00666072,-0.00269263,-0.00028343,0.00118098,0.00184233,-0.00113374,-0.00259815,-0.00585765,-0.00651900,-0.00661348,-0.00486563,-0.00292883,-0.00132270,-0.00009448,-0.00009448,-0.00056687,-0.00108650,-0.00179509,-0.00207852,-0.00132270,-0.00061411,0.00094478,0.00165337,0.00292883,0.00288159,0.00354294,0.00288159,0.00245644,0.00165337,0.00075583,-0.00009448,-0.00009448,-0.00056687,0.00047239,0.00075583,0.00122822,0.00075583,-0.00028343,-0.00132270,-0.00099202,0.00047239,0.00363741,0.00637728,0.00864476,0.00930611,0.00940059,0.00921163,0.00769998,0.00637728,0.00245644,0.00042515,-0.00340122,-0.00434600,-0.00557422,-0.00661348,-0.00633004,-0.00647176,-0.00462944,-0.00250367,-0.00051963,0.00118098,0.00203128,0.00255091,0.00340122,0.00368465,0.00330674,0.00212576,0.00023620,-0.00165337,-0.00240920,-0.00321226,-0.00160613,-0.00056687,0.00151165,0.00288159,0.00373189,0.00410980,0.00458220,0.00415704,0.00420428,0.00330674,0.00240920,0.00188957,0.00151165,0.00155889,0.00184233,0.00146441,0.00127546,0.00108650,0.00070859,0.00047239,0.00009448,-0.00151165,-0.00141717,-0.00231472,-0.00127546,-0.00108650,0.00000000,-0.00014172,0.00061411,0.00099202,0.00231472,0.00316502,0.00434600,0.00429876,0.00429876,0.00396809,0.00335398,0.00278711,0.00259815,0.00226748,0.00316502,0.00349570,0.00477115,0.00543250,0.00618833,0.00628280,0.00590489,0.00571594,0.00538526,0.00505459,0.00519630,0.00415704,0.00396809,0.00311778,0.00240920,0.00245644,0.00250367,0.00259815,0.00344846,0.00349570,0.00462944,0.00514907,0.00633004,0.00599937,0.00637728,0.00491287,0.00387361,0.00193680,0.00061411,0.00056687,0.00146441,0.00434600,0.00703863,0.01015641,0.01171531,0.01214046,0.01072328,0.00878648,0.00576317,0.00325950,0.00089754,0.00000000,-0.00089754,-0.00080307,-0.00051963,-0.00004724,0.00160613,0.00203128,0.00335398,0.00311778,0.00387361,0.00340122,0.00396809,0.00278711,0.00278711,0.00127546,0.00127546,0.00136993,0.00255091,0.00363741,0.00439324,0.00472391,0.00444048,0.00415704,0.00302330,0.00193680,0.00070859,0.00023620,-0.00004724,0.00066135,0.00051963,0.00136993,0.00174785,0.00264539,0.00354294,0.00255091,0.00061411,-0.00222024,-0.00467667,-0.00496011,-0.00382637,-0.00184233,0.00042515,0.00103926,0.00132270,0.00085030,0.00075583,0.00075583,0.00118098,0.00094478,0.00028343,-0.00080307,-0.00212576,-0.00155889,-0.00099202,0.00146441,0.00198404,0.00302330,0.00165337,0.00184233,0.00141717,0.00203128,0.00174785,0.00141717,-0.00023620,-0.00066135,-0.00099202,-0.00042515,0.00028343,0.00118098,0.00160613,0.00217300,0.00255091,0.00165337,0.00212576,0.00127546,0.00250367,0.00434600,0.00576317,0.00751102,0.00689691,0.00566870,0.00410980,0.00174785,0.00070859,-0.00127546,-0.00349570,-0.00472391,-0.00736931,-0.00732207,-0.00821961,-0.00670796,-0.00533802,-0.00349570,-0.00217300,-0.00179509,-0.00240920,-0.00434600,-0.00623557,-0.00916439,-0.01062881,-0.01228218,-0.01289628,-0.01317972,-0.01294352,-0.01176254,-0.01001470,-0.00793617,-0.00590489,-0.00547974,-0.00510183,-0.00651900,-0.00703863,-0.00708587,-0.00675520,-0.00510183,-0.00434600,-0.00321226,-0.00307054,-0.00297607,-0.00349570,-0.00283435,-0.00217300,0.00037791,0.00340122,0.00656624,0.00992022,0.01048709,0.01081776,0.00831409,0.00576317,0.00292883,0.00047239,-0.00127546,-0.00255091,-0.00325950,-0.00387361,-0.00311778,-0.00335398,-0.00278711,-0.00387361,-0.00500735,-0.00670796,-0.00736931,-0.00703863,-0.00562146,-0.00368465,-0.00273987,-0.00184233,-0.00264539,-0.00325950,-0.00566870,-0.00784170,-0.01029813,-0.01180978,-0.01176254,-0.01025089,-0.00760550,-0.00368465,-0.00089754,0.00259815,0.00396809,0.00486563,0.00462944,0.00373189,0.00236196,0.00056687,-0.00136993,-0.00292883,-0.00453496,-0.00529078,-0.00637728,-0.00651900,-0.00727483,-0.00684967,-0.00633004,-0.00477115,-0.00321226,-0.00245644,-0.00174785,-0.00198404,-0.00085030,0.00037791,0.00193680,0.00335398,0.00283435,0.00278711,0.00179509,0.00113374,0.00099202,0.00042515,0.00018896,0.00047239,0.00023620,0.00099202,0.00103926,0.00151165,0.00051963,0.00070859,-0.00146441,-0.00174785,-0.00415704,-0.00481839,-0.00581041,-0.00524354,-0.00477115,-0.00349570,-0.00307054,-0.00278711,-0.00245644,-0.00311778,-0.00245644,-0.00307054,-0.00269263,-0.00288159,-0.00269263,-0.00212576,-0.00198404,-0.00170061,-0.00160613,-0.00160613,-0.00028343,0.00042515,0.00250367,0.00307054,0.00448772,0.00335398,0.00335398,0.00184233,0.00132270,0.00165337,0.00132270,0.00222024,0.00198404,0.00179509,0.00155889,0.00051963,0.00061411,-0.00056687,0.00018896,0.00000000,0.00099202,0.00207852,0.00311778,0.00462944,0.00585765,0.00746378,0.00793617,0.00878648,0.00840857,0.00784170,0.00751102,0.00680244,0.00604661,0.00543250,0.00340122,0.00188957,0.00000000,-0.00141717,-0.00269263,-0.00373189,-0.00448772,-0.00510183,-0.00415704,-0.00368465,-0.00127546,0.00037791,0.00203128,0.00363741,0.00401533,0.00453496,0.00453496,0.00396809,0.00401533,0.00335398,0.00382637,0.00335398,0.00368465,0.00321226,0.00344846,0.00307054,0.00429876,0.00453496,0.00538526,0.00538526,0.00467667,0.00363741,0.00179509,0.00056687,-0.00179509,-0.00222024,-0.00344846,-0.00302330,-0.00255091,-0.00151165,-0.00080307,0.00028343,0.00061411,0.00174785,0.00217300,0.00363741,0.00486563,0.00642452,0.00769998,0.00821961,0.00836133,0.00713311,0.00614109,0.00368465,0.00165337,-0.00056687,-0.00179509,-0.00222024,-0.00066135,0.00113374,0.00344846,0.00576317,0.00595213,0.00633004,0.00434600,0.00316502,0.00094478,0.00014172,-0.00141717,-0.00132270,-0.00226748,-0.00198404,-0.00174785,-0.00174785,-0.00033067,-0.00047239,0.00094478,0.00127546,0.00264539,0.00297607,0.00401533,0.00349570,0.00335398,0.00193680,0.00037791,-0.00136993,-0.00377913,-0.00514907,-0.00656624,-0.00633004,-0.00614109,-0.00529078,-0.00491287,-0.00543250,-0.00623557,-0.00732207,-0.00831409,-0.00817237,-0.00831409,-0.00699139,-0.00505459,-0.00278711,0.00056687,0.00283435,0.00500735,0.00581041,0.00571594,0.00467667,0.00368465,0.00118098,0.00014172,-0.00255091,-0.00278711,-0.00448772,-0.00354294,-0.00392085,-0.00283435,-0.00231472,-0.00212576,-0.00146441,-0.00080307,-0.00009448,0.00094478,0.00155889,0.00136993,0.00136993,0.00056687,0.00023620,0.00037791,0.00099202,0.00193680,0.00349570,0.00444048,0.00576317,0.00566870,0.00576317,0.00396809,0.00330674,0.00141717,0.00103926,0.00033067,0.00108650,0.00146441,0.00264539,0.00288159,0.00330674,0.00349570,0.00401533,0.00467667,0.00543250,0.00510183,0.00486563,0.00344846,0.00288159,0.00264539,0.00269263,0.00325950,0.00382637,0.00439324,0.00514907,0.00519630,0.00505459,0.00292883,0.00056687,-0.00330674,-0.00675520,-0.00859752,-0.01020365,-0.00831409,-0.00699139,-0.00453496,-0.00217300,-0.00151165,-0.00014172,-0.00051963,-0.00080307,-0.00273987,-0.00401533,-0.00642452,-0.00637728,-0.00684967,-0.00467667,-0.00363741,-0.00155889,-0.00103926,-0.00047239,-0.00018896,-0.00061411,-0.00085030,-0.00179509,-0.00226748,-0.00259815,-0.00207852,-0.00136993,-0.00004724,0.00061411,0.00080307,0.00051963,-0.00075583,-0.00151165,-0.00264539,-0.00236196,-0.00184233,-0.00014172,0.00136993,0.00240920,0.00368465,0.00311778,0.00354294,0.00203128,0.00174785,-0.00023620,-0.00066135,-0.00203128,-0.00226748,-0.00245644,-0.00283435,-0.00184233,-0.00188957,-0.00004724,-0.00009448,0.00103926,0.00056687,0.00028343,0.00033067,-0.00004724,0.00151165,0.00292883,0.00543250,0.00826685,0.01006194,0.01162083,0.01152635,0.01048709,0.00878648,0.00614109,0.00415704,0.00151165,0.00094478,0.00051963,0.00146441,0.00330674,0.00363741,0.00486563,0.00410980,0.00444048,0.00410980,0.00467667,0.00514907,0.00547974,0.00604661,0.00524354,0.00477115,0.00288159,0.00089754,-0.00070859,-0.00273987,-0.00273987,-0.00297607,-0.00184233,-0.00113374,-0.00004724,0.00004724,-0.00009448,-0.00075583,-0.00179509,-0.00165337,-0.00188957,-0.00136993,-0.00165337,-0.00273987,-0.00425152,-0.00618833,-0.00708587,-0.00722759,-0.00557422,-0.00377913,-0.00127546,-0.00023620,-0.00009448,-0.00184233,-0.00410980,-0.00722759,-0.00911715,-0.01110120,-0.01053433,-0.01034537,-0.00765274,-0.00651900,-0.00368465,-0.00255091,-0.00042515,0.00113374,0.00273987,0.00368465,0.00382637,0.00359017,0.00141717,0.00000000,-0.00302330,-0.00410980,-0.00524354,-0.00429876,-0.00255091,-0.00014172,0.00193680,0.00330674,0.00429876,0.00481839,0.00604661,0.00633004,0.00666072,0.00661348,0.00519630,0.00439324,0.00316502,0.00118098,0.00075583,-0.00217300,-0.00184233,-0.00311778,-0.00122822,-0.00075583,0.00122822,0.00075583,0.00075583,-0.00085030,-0.00170061,-0.00264539,-0.00278711,-0.00269263,-0.00240920,-0.00113374,-0.00085030,0.00033067,0.00066135,0.00004724,-0.00018896,-0.00122822,-0.00207852,-0.00132270,-0.00127546,0.00089754,0.00188957,0.00359017,0.00382637,0.00434600,0.00359017,0.00325950,0.00231472,0.00118098,-0.00009448,-0.00108650,-0.00188957,-0.00127546,-0.00070859,0.00080307,0.00236196,0.00321226,0.00425152,0.00363741,0.00330674,0.00231472,0.00160613,0.00151165,0.00141717,0.00188957,0.00217300,0.00278711,0.00259815,0.00259815,0.00099202,0.00014172,-0.00141717,-0.00155889,-0.00184233,-0.00108650,-0.00047239,0.00061411,0.00193680,0.00325950,0.00467667,0.00604661,0.00628280,0.00718035,0.00661348,0.00642452,0.00514907,0.00377913,0.00165337,0.00075583,-0.00047239,-0.00009448,-0.00037791,0.00047239,0.00085030,0.00212576,0.00302330,0.00392085,0.00505459,0.00519630,0.00557422,0.00467667,0.00410980,0.00259815,0.00099202,0.00018896,-0.00122822,-0.00056687,-0.00033067,0.00127546,0.00207852,0.00368465,0.00392085,0.00467667,0.00496011,0.00533802,0.00529078,0.00458220,0.00307054,0.00080307,-0.00066135,-0.00203128,-0.00203128,-0.00165337,-0.00075583,-0.00014172,0.00004724,0.00014172,-0.00023620,-0.00037791,-0.00075583,-0.00108650,-0.00023620,0.00075583,0.00255091,0.00448772,0.00552698,0.00623557,0.00543250,0.00491287,0.00316502,0.00330674,0.00236196,0.00288159,0.00231472,0.00170061,0.00089754,0.00037791,0.00014172,0.00066135,0.00146441,0.00155889,0.00188957,0.00047239,0.00009448,-0.00155889,-0.00236196,-0.00250367,-0.00288159,-0.00155889,-0.00085030,0.00028343,0.00042515,0.00037791,-0.00118098,-0.00193680,-0.00349570,-0.00425152,-0.00486563,-0.00524354,-0.00500735,-0.00538526,-0.00458220,-0.00481839,-0.00363741,-0.00415704,-0.00354294,-0.00510183,-0.00604661,-0.00751102,-0.00940059,-0.01001470,-0.01138463,-0.01077052,-0.00977850,-0.00741654,-0.00477115,-0.00307054,-0.00250367,-0.00307054,-0.00458220,-0.00637728,-0.00798341,-0.01010917,-0.01152635,-0.01270733,-0.01251837,-0.01105396,-0.00878648,-0.00571594,-0.00377913,-0.00288159,-0.00288159,-0.00505459,-0.00647176,-0.00902267,-0.01029813,-0.01180978,-0.01190426,-0.01261285,-0.01190426,-0.01114844,-0.00973126,-0.00817237,-0.00675520,-0.00623557,-0.00571594,-0.00529078,-0.00491287,-0.00392085,-0.00349570,-0.00316502,-0.00335398,-0.00396809,-0.00453496,-0.00396809,-0.00335398,-0.00080307,0.00037791,0.00188957,-0.00014172,-0.00170061,-0.00543250,-0.00656624,-0.00628280,-0.00467667,-0.00170061,-0.00075583,-0.00018896,-0.00207852,-0.00453496,-0.00751102,-0.00935335,-0.01072328,-0.00930611,-0.00774722,-0.00496011,-0.00245644,-0.00188957,-0.00085030,-0.00132270,-0.00113374,-0.00085030,-0.00061411,-0.00127546,-0.00155889,-0.00335398,-0.00373189,-0.00462944,-0.00448772,-0.00510183,-0.00557422,-0.00755826,-0.00855028,-0.01062881,-0.01058157,-0.01039261,-0.00940059,-0.00869200,-0.00850304,-0.00925887,-0.00911715,-0.00949507,-0.00840857,-0.00798341,-0.00751102,-0.00746378,-0.00755826,-0.00675520,-0.00609385,-0.00496011,-0.00425152,-0.00410980,-0.00382637,-0.00410980,-0.00344846,-0.00330674,-0.00311778,-0.00330674,-0.00415704,-0.00429876,-0.00453496,-0.00349570,-0.00255091,-0.00184233,-0.00136993,-0.00255091,-0.00292883,-0.00344846,-0.00245644,0.00009448,0.00288159,0.00651900,0.00765274,0.00888096,0.00718035,0.00571594,0.00335398,0.00127546,-0.00009448,-0.00094478,-0.00155889,-0.00179509,-0.00222024,-0.00240920,-0.00184233,-0.00240920,-0.00193680,-0.00363741,-0.00500735,-0.00751102,-0.00897544,-0.00958954,-0.00968402,-0.00831409,-0.00760550,-0.00595213,-0.00462944,-0.00311778,-0.00188957,-0.00061411,-0.00004724,0.00085030,0.00085030,0.00047239,-0.00103926,-0.00250367,-0.00382637,-0.00420428,-0.00415704,-0.00340122,-0.00307054,-0.00203128,-0.00165337,0.00004724,0.00004724,0.00042515,-0.00113374,-0.00349570,-0.00491287,-0.00656624,-0.00557422,-0.00420428,-0.00127546,0.00151165,0.00453496,0.00694415,0.00779446,0.00869200,0.00784170,0.00798341,0.00812513,0.00812513,0.00883372,0.00921163,0.01072328,0.01289628,0.01577787,0.01903737,0.02036007,0.02040731,0.01771468,0.01421898,0.00982574,0.00604661,0.00236196,-0.00056687,-0.00259815,-0.00278711,-0.00094478,0.00288159,0.00637728,0.00906991,0.00949507,0.00897544,0.00699139,0.00552698,0.00373189,0.00226748,0.00141717,0.00089754,0.00174785,0.00288159,0.00392085,0.00425152,0.00410980,0.00425152,0.00425152,0.00477115,0.00415704,0.00250367,0.00099202,-0.00113374,-0.00217300,-0.00269263,-0.00292883,-0.00325950,-0.00302330,-0.00302330,-0.00203128,-0.00066135,0.00056687,0.00222024,0.00321226,0.00396809,0.00481839,0.00453496,0.00472391,0.00382637,0.00245644,0.00042515,-0.00207852,-0.00425152,-0.00500735,-0.00486563,-0.00373189,-0.00222024,-0.00165337,-0.00113374,-0.00141717,-0.00203128,-0.00307054,-0.00406257,-0.00472391,-0.00434600,-0.00311778,-0.00184233,-0.00009448,0.00042515,0.00122822,0.00127546,0.00122822,0.00108650,0.00004724,-0.00023620,-0.00004724,0.00018896,0.00207852,0.00170061,0.00259815,0.00174785,0.00141717,0.00122822,0.00066135,0.00042515,-0.00037791,-0.00122822,-0.00217300,-0.00302330,-0.00311778,-0.00297607,-0.00136993,-0.00080307,0.00108650,0.00023620,0.00061411,-0.00004724,0.00037791,0.00165337,0.00231472,0.00307054,0.00264539,0.00203128,0.00094478,0.00075583,-0.00094478,-0.00132270,-0.00359017,-0.00415704,-0.00448772,-0.00373189,-0.00240920,-0.00118098,0.00023620,0.00188957,0.00340122,0.00538526,0.00637728,0.00736931,0.00722759,0.00807789,0.00817237,0.00958954,0.00982574,0.01001470,0.00940059,0.00826685,0.00741654,0.00684967,0.00647176,0.00595213,0.00595213,0.00576317,0.00694415,0.00859752,0.01010917,0.01162083,0.01180978,0.01124291,0.01034537,0.00869200,0.00798341,0.00793617,0.00850304,0.01048709,0.01209322,0.01365211,0.01426622,0.01322696,0.01204598,0.00897544,0.00769998,0.00486563,0.00401533,0.00207852,0.00066135,-0.00070859,-0.00226748,-0.00250367,-0.00283435,-0.00203128,-0.00094478,-0.00051963,0.00141717,0.00160613,0.00359017,0.00415704,0.00500735,0.00547974,0.00623557,0.00703863,0.00840857,0.00916439,0.00925887,0.00883372,0.00746378,0.00708587,0.00623557,0.00661348,0.00642452,0.00604661,0.00524354,0.00368465,0.00292883,0.00179509,0.00136993,0.00132270,0.00118098,0.00155889,0.00231472,0.00292883,0.00491287,0.00651900,0.00817237,0.00977850,0.01039261,0.01048709,0.01043985,0.00892820,0.00727483,0.00363741,-0.00042515,-0.00533802,-0.00812513,-0.01001470,-0.00769998,-0.00529078,-0.00056687,0.00217300,0.00477115,0.00609385,0.00633004,0.00680244,0.00618833,0.00581041,0.00472391,0.00415704,0.00335398,0.00373189,0.00311778,0.00283435,0.00155889,0.00000000,-0.00127546,-0.00264539,-0.00240920,-0.00297607,-0.00151165,-0.00141717,-0.00037791,-0.00066135,-0.00056687,-0.00155889,-0.00141717,-0.00231472,-0.00146441,-0.00236196,-0.00174785,-0.00302330,-0.00335398,-0.00444048,-0.00524354,-0.00519630,-0.00566870,-0.00429876,-0.00392085,-0.00269263,-0.00283435,-0.00321226,-0.00387361,-0.00396809,-0.00354294,-0.00193680,-0.00099202,0.00099202,0.00203128,0.00368465,0.00500735,0.00557422,0.00557422,0.00462944,0.00377913,0.00335398,0.00382637,0.00496011,0.00599937,0.00736931,0.00869200,0.00987298,0.01119567,0.01072328,0.01025089,0.00798341,0.00614109,0.00387361,0.00245644,0.00170061,0.00165337,0.00264539,0.00344846,0.00472391,0.00491287,0.00543250,0.00467667,0.00458220,0.00292883,0.00222024,0.00004724,-0.00080307,-0.00217300,-0.00245644,-0.00278711,-0.00283435,-0.00269263,-0.00184233,-0.00033067,0.00066135,0.00184233,0.00127546,0.00075583,-0.00047239,-0.00165337,-0.00240920,-0.00316502,-0.00373189,-0.00382637,-0.00269263,-0.00113374,0.00170061,0.00387361,0.00557422,0.00732207,0.00850304,0.00982574,0.01133739,0.01162083,0.01058157,0.00906991,0.00519630,0.00297607,0.00004724,-0.00089754,-0.00099202,-0.00066135,0.00018896,0.00042515,0.00009448,-0.00051963,-0.00061411,0.00009448,0.00179509,0.00392085,0.00448772,0.00472391,0.00335398,0.00236196,0.00226748,0.00316502,0.00382637,0.00481839,0.00434600,0.00453496,0.00500735,0.00547974,0.00590489,0.00562146,0.00377913,0.00207852,-0.00028343,-0.00141717,-0.00193680,-0.00170061,-0.00094478,-0.00033067,-0.00004724,0.00051963,0.00028343,0.00056687,0.00108650,0.00160613,0.00259815,0.00255091,0.00283435,0.00099202,0.00075583,-0.00089754,-0.00085030,-0.00014172,0.00028343,0.00141717,0.00127546,0.00061411,0.00000000,-0.00061411,-0.00103926,-0.00042515,-0.00127546,-0.00070859,-0.00207852,-0.00269263,-0.00410980,-0.00543250,-0.00599937,-0.00647176,-0.00529078,-0.00396809,-0.00179509,-0.00004724,0.00170061,0.00340122,0.00547974,0.00675520,0.00769998,0.00703863,0.00637728,0.00486563,0.00420428,0.00330674,0.00255091,0.00283435,0.00278711,0.00448772,0.00590489,0.00765274,0.00873924,0.00892820,0.00859752,0.00741654,0.00628280,0.00439324,0.00330674,0.00217300,0.00222024,0.00302330,0.00425152,0.00599937,0.00670796,0.00769998,0.00689691,0.00618833,0.00486563,0.00344846,0.00188957,-0.00056687,-0.00387361,-0.00765274,-0.01010917,-0.01152635,-0.01058157,-0.00855028,-0.00628280,-0.00410980,-0.00217300,-0.00099202,0.00000000,0.00056687,0.00094478,0.00103926,0.00174785,0.00179509,0.00203128,0.00193680,0.00141717,0.00203128,0.00273987,0.00392085,0.00472391,0.00453496,0.00439324,0.00316502,0.00344846,0.00278711,0.00415704,0.00481839,0.00680244,0.00765274,0.00831409,0.00751102,0.00647176,0.00562146,0.00514907,0.00547974,0.00538526,0.00462944,0.00349570,0.00273987,0.00179509,0.00151165,0.00066135,-0.00037791,-0.00066135,-0.00023620,0.00146441,0.00377913,0.00628280,0.00788894,0.00859752,0.00817237,0.00609385,0.00363741,0.00070859,-0.00122822,-0.00174785,-0.00165337,-0.00108650,-0.00070859,-0.00066135,-0.00051963,-0.00028343,-0.00018896,-0.00014172,-0.00023620,-0.00085030,-0.00075583,-0.00085030,-0.00018896,0.00080307,0.00203128,0.00368465,0.00496011,0.00543250,0.00481839,0.00415704,0.00226748,0.00193680,0.00066135,0.00004724,0.00014172,0.00066135,0.00297607,0.00505459,0.00713311,0.00689691,0.00647176,0.00401533,0.00368465,0.00212576,0.00259815,0.00203128,0.00179509,0.00174785,0.00146441,0.00325950,0.00406257,0.00670796,0.00840857,0.01039261,0.01157359,0.01166807,0.01015641,0.00850304,0.00552698,0.00325950,0.00118098,0.00000000,0.00014172,0.00108650,0.00217300,0.00387361,0.00349570,0.00354294,0.00217300,0.00132270,0.00170061,0.00136993,0.00203128,0.00066135,-0.00070859,-0.00349570,-0.00510183,-0.00637728,-0.00618833,-0.00491287,-0.00387361,-0.00198404,-0.00179509,-0.00009448,0.00061411,0.00226748,0.00359017,0.00396809,0.00425152,0.00340122,0.00302330,0.00325950,0.00363741,0.00566870,0.00585765,0.00694415,0.00618833,0.00543250,0.00486563,0.00458220,0.00387361,0.00410980,0.00231472,0.00160613,-0.00089754,-0.00141717,-0.00311778,-0.00217300,-0.00264539,-0.00184233,-0.00203128,-0.00236196,-0.00392085,-0.00505459,-0.00736931,-0.00855028,-0.00883372,-0.00798341,-0.00585765,-0.00363741,-0.00155889,-0.00080307,-0.00094478,-0.00193680,-0.00288159,-0.00273987,-0.00188957,0.00000000,0.00141717,0.00340122,0.00354294,0.00410980,0.00316502,0.00179509,0.00009448,-0.00269263,-0.00401533,-0.00623557,-0.00614109,-0.00703863,-0.00585765,-0.00472391,-0.00217300,0.00023620,0.00198404,0.00240920,0.00155889,0.00051963,0.00033067,0.00108650,0.00264539,0.00349570,0.00250367,0.00108650,-0.00170061,-0.00354294,-0.00500735,-0.00547974,-0.00533802,-0.00396809,-0.00207852,0.00080307,0.00325950,0.00434600,0.00458220,0.00368465,0.00240920,0.00212576,0.00042515,0.00037791,-0.00222024,-0.00340122,-0.00538526,-0.00642452,-0.00571594,-0.00547974,-0.00377913,-0.00359017,-0.00288159,-0.00368465,-0.00382637,-0.00444048,-0.00519630,-0.00571594,-0.00765274,-0.00883372,-0.01077052,-0.01124291,-0.01091224,-0.00949507,-0.00670796,-0.00410980,-0.00108650,0.00103926,0.00259815,0.00368465,0.00420428,0.00491287,0.00496011,0.00491287,0.00387361,0.00311778,0.00203128,0.00155889,0.00155889,0.00080307,0.00051963,-0.00141717,-0.00222024,-0.00373189,-0.00359017,-0.00377913,-0.00278711,-0.00240920,-0.00108650,0.00009448,0.00136993,0.00240920,0.00255091,0.00193680,0.00118098,-0.00061411,-0.00122822,-0.00188957,-0.00132270,-0.00042515,0.00080307,0.00103926,0.00141717,-0.00023620,-0.00014172,-0.00108650,-0.00028343,0.00037791,0.00004724,0.00085030,0.00080307,0.00259815,0.00420428,0.00571594,0.00581041,0.00406257,0.00184233,-0.00042515,-0.00085030,-0.00089754,0.00014172,0.00042515,-0.00004724,0.00018896,-0.00108650,-0.00080307,-0.00127546,-0.00103926,-0.00018896,0.00103926,0.00231472,0.00316502,0.00250367,0.00146441,-0.00042515,-0.00047239,0.00000000,0.00207852,0.00429876,0.00547974,0.00656624,0.00576317,0.00543250,0.00453496,0.00382637,0.00359017,0.00269263,0.00250367,0.00127546,0.00061411,-0.00070859,-0.00155889,-0.00165337,-0.00113374,0.00051963,0.00311778,0.00562146,0.00718035,0.00798341,0.00618833,0.00458220,0.00188957,0.00028343,-0.00089754,-0.00170061,-0.00236196,-0.00273987,-0.00382637,-0.00410980,-0.00500735,-0.00557422,-0.00585765,-0.00651900,-0.00684967,-0.00732207,-0.00840857,-0.00906991,-0.01010917,-0.01010917,-0.00958954,-0.00864476,-0.00722759,-0.00680244,-0.00590489,-0.00637728,-0.00590489,-0.00557422,-0.00496011,-0.00311778,-0.00179509,-0.00018896,0.00108650,0.00089754,0.00061411,-0.00009448,-0.00146441,-0.00155889,-0.00278711,-0.00288159,-0.00434600,-0.00448772,-0.00576317,-0.00514907,-0.00533802,-0.00429876,-0.00335398,-0.00160613,-0.00056687,0.00113374,0.00066135,0.00094478,-0.00085030,-0.00141717,-0.00344846,-0.00396809,-0.00491287,-0.00529078,-0.00547974,-0.00585765,-0.00628280,-0.00651900,-0.00623557,-0.00604661,-0.00486563,-0.00448772,-0.00439324,-0.00519630,-0.00656624,-0.00788894,-0.00916439,-0.00940059,-0.00982574,-0.00855028,-0.00807789,-0.00585765,-0.00410980,-0.00174785,0.00037791,0.00179509,0.00259815,0.00245644,0.00198404,0.00042515,-0.00099202,-0.00259815,-0.00439324,-0.00581041,-0.00708587,-0.00793617,-0.00769998,-0.00689691,-0.00505459,-0.00344846,-0.00179509,-0.00136993,-0.00103926,-0.00132270,-0.00136993,-0.00136993,-0.00198404,-0.00174785,-0.00325950,-0.00344846,-0.00415704,-0.00439324,-0.00373189,-0.00335398,-0.00255091,-0.00212576,-0.00160613,-0.00174785,-0.00179509,-0.00240920,-0.00250367,-0.00363741,-0.00311778,-0.00486563,-0.00396809,-0.00510183,-0.00406257,-0.00311778,-0.00188957,0.00042515,0.00155889,0.00344846,0.00410980,0.00514907,0.00552698,0.00500735,0.00439324,0.00184233,0.00037791,-0.00255091,-0.00307054,-0.00401533,-0.00259815,-0.00108650,0.00118098,0.00335398,0.00425152,0.00510183,0.00401533,0.00325950,0.00165337,0.00113374,-0.00004724,-0.00103926,-0.00278711,-0.00505459,-0.00680244,-0.00826685,-0.00807789,-0.00656624,-0.00382637,-0.00047239,0.00245644,0.00458220,0.00514907,0.00462944,0.00359017,0.00207852,0.00089754,0.00009448,-0.00099202,-0.00146441,-0.00250367,-0.00264539,-0.00344846,-0.00316502,-0.00302330,-0.00236196,-0.00179509,-0.00174785,-0.00122822,-0.00141717,-0.00174785,-0.00184233,-0.00330674,-0.00406257,-0.00533802,-0.00633004,-0.00628280,-0.00571594,-0.00444048,-0.00392085,-0.00344846,-0.00453496,-0.00543250,-0.00609385,-0.00647176,-0.00543250,-0.00429876,-0.00316502,-0.00297607,-0.00377913,-0.00628280,-0.00930611,-0.01322696,-0.01625026,-0.01847050,-0.01903737,-0.01861222,-0.01639198,-0.01525824,-0.01228218,-0.01166807,-0.00963678,-0.00873924,-0.00821961,-0.00703863,-0.00760550,-0.00746378,-0.00774722,-0.00840857,-0.00807789,-0.00836133,-0.00779446,-0.00736931,-0.00684967,-0.00647176,-0.00599937,-0.00651900,-0.00604661,-0.00694415,-0.00656624,-0.00736931,-0.00774722,-0.00944783,-0.01043985,-0.01223494,-0.01199874,-0.01133739,-0.00930611,-0.00708587,-0.00510183,-0.00462944,-0.00401533,-0.00576317,-0.00637728,-0.00798341,-0.00855028,-0.00855028,-0.00807789,-0.00618833,-0.00486563,-0.00307054,-0.00302330,-0.00425152,-0.00647176,-0.00963678,-0.01147911,-0.01284904,-0.01199874,-0.01029813,-0.00812513,-0.00552698,-0.00387361,-0.00217300,-0.00122822,0.00009448,0.00122822,0.00245644,0.00245644,0.00174785,-0.00099202,-0.00377913,-0.00746378,-0.00987298,-0.01067604,-0.01001470,-0.00722759,-0.00462944,-0.00174785,-0.00122822,-0.00103926,-0.00273987,-0.00429876,-0.00500735,-0.00590489,-0.00571594,-0.00538526,-0.00557422,-0.00496011,-0.00514907,-0.00453496,-0.00514907,-0.00458220,-0.00472391,-0.00273987,-0.00085030,0.00193680,0.00368465,0.00448772,0.00396809,0.00207852,0.00094478,-0.00033067,-0.00051963,-0.00061411,-0.00198404,-0.00264539,-0.00519630,-0.00581041,-0.00675520,-0.00618833,-0.00510183,-0.00462944,-0.00387361,-0.00425152,-0.00481839,-0.00585765,-0.00718035,-0.00864476,-0.01015641,-0.01143187,-0.01223494,-0.01308524,-0.01303800,-0.01440794,-0.01431346,-0.01492757,-0.01407726,-0.01270733,-0.01095948,-0.00940059,-0.00840857,-0.00769998,-0.00760550,-0.00713311,-0.00699139,-0.00614109,-0.00647176,-0.00618833,-0.00684967,-0.00699139,-0.00656624,-0.00557422,-0.00387361,-0.00146441,0.00023620,0.00141717,0.00151165,0.00151165,0.00103926,0.00075583,0.00047239,-0.00033067,-0.00061411,-0.00080307,-0.00028343,0.00108650,0.00240920,0.00396809,0.00396809,0.00401533,0.00269263,0.00198404,0.00122822,0.00061411,0.00132270,0.00061411,0.00236196,0.00179509,0.00311778,0.00368465,0.00425152,0.00510183,0.00505459,0.00429876,0.00373189,0.00226748,0.00146441,0.00070859,0.00037791,0.00023620,0.00099202,0.00118098,0.00136993,0.00042515,-0.00089754,-0.00207852,-0.00113374,0.00000000,0.00188957,0.00226748,0.00066135,-0.00014172,-0.00080307,0.00198404,0.00420428,0.00633004,0.00547974,0.00340122,0.00193680,0.00288159,0.00675520,0.01105396,0.01454965,0.01521100,0.01393554,0.01204598,0.00925887,0.00836133,0.00562146,0.00500735,0.00311778,0.00269263,0.00259815,0.00330674,0.00410980,0.00481839,0.00566870,0.00514907,0.00576317,0.00510183,0.00642452,0.00755826,0.00954231,0.01129015,0.01176254,0.01110120,0.00982574,0.00836133,0.00769998,0.00769998,0.00807789,0.00831409,0.00779446,0.00642452,0.00420428,0.00245644,0.00122822,0.00127546,0.00255091,0.00368465,0.00514907,0.00477115,0.00363741,0.00141717,-0.00113374,-0.00292883,-0.00297607,-0.00207852,0.00014172,0.00217300,0.00297607,0.00359017,0.00217300,0.00179509,0.00042515,0.00028343,-0.00042515,0.00023620,-0.00004724,0.00042515,-0.00018896,-0.00203128,-0.00288159,-0.00453496,-0.00359017,-0.00231472,-0.00051963,0.00089754,0.00113374,0.00136993,0.00146441,0.00108650,0.00037791,-0.00212576,-0.00387361,-0.00547974,-0.00524354,-0.00368465,-0.00288159,-0.00188957,-0.00231472,-0.00141717,-0.00042515,0.00198404,0.00344846,0.00467667,0.00477115,0.00439324,0.00368465,0.00222024,-0.00042515,-0.00245644,-0.00458220,-0.00406257,-0.00226748,0.00099202,0.00340122,0.00514907,0.00429876,0.00321226,0.00103926,-0.00094478,-0.00231472,-0.00354294,-0.00392085,-0.00410980,-0.00396809,-0.00429876,-0.00448772,-0.00538526,-0.00618833,-0.00722759,-0.00821961,-0.00892820,-0.00892820,-0.00906991,-0.00708587,-0.00604661,-0.00212576,0.00061411,0.00354294,0.00557422,0.00524354,0.00538526,0.00458220,0.00500735,0.00581041,0.00637728,0.00552698,0.00429876,0.00118098,-0.00080307,-0.00292883,-0.00354294,-0.00392085,-0.00302330,-0.00330674,-0.00278711,-0.00396809,-0.00458220,-0.00557422,-0.00604661,-0.00651900,-0.00718035,-0.00755826,-0.00855028,-0.00845581,-0.00859752,-0.00769998,-0.00633004,-0.00448772,-0.00207852,0.00000000,0.00188957,0.00103926,0.00037791,-0.00226748,-0.00302330,-0.00269263,-0.00165337,-0.00080307,-0.00080307,-0.00226748,-0.00302330,-0.00415704,-0.00392085,-0.00415704,-0.00396809,-0.00359017,-0.00273987,-0.00141717,0.00000000,-0.00033067,-0.00151165,-0.00382637,-0.00675520,-0.00840857,-0.01006194,-0.01010917,-0.00987298,-0.00831409,-0.00703863,-0.00477115,-0.00415704,-0.00340122,-0.00467667,-0.00581041,-0.00718035,-0.00821961,-0.00788894,-0.00708587,-0.00576317,-0.00359017,-0.00250367,-0.00061411,-0.00004724,0.00023620,-0.00004724,-0.00151165,-0.00240920,-0.00330674,-0.00283435,-0.00103926,0.00042515,0.00146441,0.00174785,0.00047239,0.00028343,-0.00089754,-0.00075583,-0.00113374,-0.00051963,0.00037791,0.00325950,0.00651900,0.01067604,0.01218770,0.01185702,0.00774722,0.00344846,-0.00174785,-0.00401533,-0.00614109,-0.00599937,-0.00628280,-0.00576317,-0.00571594,-0.00581041,-0.00642452,-0.00821961,-0.00996746,-0.01119567,-0.01067604,-0.00817237,-0.00505459,-0.00250367,-0.00075583,-0.00028343,0.00132270,0.00278711,0.00505459,0.00599937,0.00547974,0.00444048,0.00325950,0.00359017,0.00524354,0.00689691,0.00902267,0.00911715,0.00921163,0.00821961,0.00703863,0.00590489,0.00448772,0.00340122,0.00245644,0.00184233,0.00132270,0.00146441,0.00113374,0.00118098,0.00042515,0.00028343,-0.00070859,-0.00028343,-0.00127546,-0.00122822,-0.00245644,-0.00240920,-0.00184233,-0.00023620,0.00231472,0.00387361,0.00496011,0.00396809,0.00330674,0.00118098,0.00061411,-0.00066135,-0.00127546,-0.00179509,-0.00179509,-0.00207852,-0.00132270,-0.00198404,-0.00198404,-0.00278711,-0.00330674,-0.00368465,-0.00420428,-0.00472391,-0.00529078,-0.00510183,-0.00477115,-0.00316502,-0.00179509,-0.00009448,0.00108650,0.00151165,0.00165337,0.00066135,0.00018896,-0.00118098,-0.00170061,-0.00255091,-0.00288159,-0.00340122,-0.00311778,-0.00373189,-0.00420428,-0.00547974,-0.00694415,-0.00637728,-0.00604661,-0.00288159,-0.00099202,0.00103926,0.00240920,0.00255091,0.00354294,0.00392085,0.00444048,0.00477115,0.00529078,0.00590489,0.00774722,0.00769998,0.00788894,0.00510183,0.00359017,0.00151165,0.00188957,0.00269263,0.00382637,0.00396809,0.00387361,0.00307054,0.00307054,0.00292883,0.00363741,0.00396809,0.00467667,0.00514907,0.00524354,0.00510183,0.00444048,0.00382637,0.00283435,0.00259815,0.00203128,0.00207852,0.00226748,0.00278711,0.00396809,0.00373189,0.00307054,0.00066135,-0.00132270,-0.00236196,-0.00127546,0.00089754,0.00349570,0.00533802,0.00609385,0.00637728,0.00713311,0.00760550,0.00807789,0.00779446,0.00670796,0.00618833,0.00628280,0.00755826,0.00902267,0.00963678,0.00930611,0.00793617,0.00699139,0.00581041,0.00595213,0.00566870,0.00736931,0.00944783,0.01261285,0.01459689,0.01421898,0.01119567,0.00713311,0.00448772,0.00410980,0.00604661,0.00845581,0.00944783,0.00963678,0.00855028,0.00784170,0.00699139,0.00623557,0.00491287,0.00429876,0.00472391,0.00547974,0.00628280,0.00656624,0.00543250,0.00590489,0.00637728,0.00873924,0.00897544,0.00930611,0.00647176,0.00486563,0.00330674,0.00311778,0.00382637,0.00377913,0.00453496,0.00368465,0.00467667,0.00429876,0.00514907,0.00477115,0.00387361,0.00085030,-0.00330674,-0.00949507,-0.01308524,-0.01473861,-0.01029813,-0.00354294,0.00486563,0.01081776,0.01308524,0.01218770,0.00869200,0.00453496,-0.00070859,-0.00429876,-0.00840857,-0.00888096,-0.00878648,-0.00581041,-0.00278711,0.00004724,0.00198404,0.00226748,0.00151165,0.00009448,-0.00174785,-0.00264539,-0.00288159,-0.00165337,0.00085030,0.00420428,0.00732207,0.01053433,0.01256561,0.01417174,0.01483309,0.01525824,0.01497481,0.01591959,0.01568339,0.01643922,0.01521100,0.01341591,0.00958954,0.00529078,0.00070859,-0.00354294,-0.00529078,-0.00722759,-0.00628280,-0.00599937,-0.00486563,-0.00302330,-0.00075583,0.00245644,0.00604661,0.00798341,0.00817237,0.00675520,0.00297607,0.00056687,-0.00255091,-0.00340122,-0.00392085,-0.00316502,-0.00307054,-0.00264539,-0.00292883,-0.00311778,-0.00240920,-0.00236196,-0.00118098,-0.00141717,-0.00018896,0.00089754,0.00382637,0.00595213,0.00793617,0.00675520,0.00439324,0.00023620,-0.00302330,-0.00496011,-0.00529078,-0.00439324,-0.00212576,0.00018896,0.00335398,0.00410980,0.00401533,0.00094478,-0.00179509,-0.00368465,-0.00307054,-0.00085030,0.00203128,0.00392085,0.00453496,0.00396809,0.00335398,0.00307054,0.00354294,0.00425152,0.00462944,0.00410980,0.00264539,0.00160613,0.00028343,0.00207852,0.00401533,0.00736931,0.01025089,0.01138463,0.01275457,0.01185702,0.01232941,0.00973126,0.00708587,0.00170061,-0.00401533,-0.00746378,-0.00864476,-0.00666072,-0.00269263,0.00113374,0.00382637,0.00557422,0.00585765,0.00618833,0.00651900,0.00703863,0.00703863,0.00821961,0.00793617,0.00836133,0.00727483,0.00566870,0.00325950,0.00193680,0.00099202,0.00231472,0.00297607,0.00392085,0.00368465,0.00297607,0.00302330,0.00307054,0.00434600,0.00444048,0.00377913,0.00226748,0.00004724,-0.00184233,-0.00335398,-0.00538526,-0.00609385,-0.00760550,-0.00788894,-0.00798341,-0.00689691,-0.00439324,-0.00165337,0.00259815,0.00477115,0.00680244,0.00618833,0.00552698,0.00335398,0.00236196,0.00033067,-0.00051963,-0.00141717,-0.00179509,-0.00113374,-0.00075583,0.00023620,0.00018896,0.00094478,0.00113374,0.00188957,0.00165337,0.00085030,-0.00028343,-0.00212576,-0.00132270,-0.00136993,0.00132270,0.00283435,0.00491287,0.00618833,0.00751102,0.00779446,0.00807789,0.00680244,0.00557422,0.00321226,0.00151165,-0.00033067,-0.00155889,-0.00273987,-0.00340122,-0.00481839,-0.00529078,-0.00656624,-0.00623557,-0.00496011,-0.00288159,-0.00033067,0.00080307,0.00089754,0.00023620,-0.00118098,-0.00250367,-0.00349570,-0.00472391,-0.00396809,-0.00288159,-0.00028343,0.00255091,0.00491287,0.00680244,0.00803065,0.00902267,0.00987298,0.00992022,0.00935335,0.00689691,0.00344846,-0.00170061,-0.00651900,-0.00949507,-0.00840857,-0.00292883,0.00566870,0.01379383,0.01785639,0.01672265,0.01086500,0.00226748,-0.00538526,-0.01190426,-0.01563615,-0.01587235,-0.01426622,-0.00992022,-0.00585765,-0.00226748,-0.00009448,0.00103926,0.00113374,-0.00014172,-0.00269263,-0.00585765,-0.00878648,-0.00906991,-0.00817237,-0.00519630,-0.00236196,0.00014172,0.00354294,0.00529078,0.00623557,0.00425152,0.00136993,0.00118098,0.00486563,0.01058157,0.01251837,0.00406257,-0.01332144,-0.03339807,-0.04634159,-0.04402687,-0.02839072,-0.00547974,0.01615578,0.03075268,0.03689376,0.03594898,0.02820176,0.01662818,0.00231472,-0.01006194,-0.01795087,-0.02040731,-0.01818707,-0.01506928,-0.01157359,-0.00883372,-0.00642452,-0.00453496,-0.00458220,-0.00736931,-0.01147911,-0.01653370,-0.01875394,-0.01847050,-0.01506928,-0.00949507,-0.00382637,0.00240920,0.00675520,0.01081776,0.01299076,0.01317972,0.01237665,0.00883372,0.00609385,0.00273987,0.00259815,0.00373189,0.00765274,0.01176254,0.01445518,0.01606131,0.01469137,0.01180978,0.00760550,0.00245644,0.00018896,-0.00037791,0.00387361,0.00935335,0.01398278,0.01544720,0.01214046,0.00722759,0.00240920,0.00118098,0.00363741,0.00807789,0.01209322,0.01280181,0.01006194,0.00420428,-0.00236196,-0.00836133,-0.01180978,-0.01374659,-0.01308524,-0.01223494,-0.00992022,-0.00765274,-0.00429876,-0.00132270,0.00217300,0.00415704,0.00500735,0.00406257,0.00056687,-0.00255091,-0.00604661,-0.00642452,-0.00496011,-0.00136993,0.00089754,0.00340122,0.00165337,0.00174785,-0.00023620,0.00070859,0.00155889,0.00382637,0.00529078,0.00661348,0.00628280,0.00628280,0.00519630,0.00538526,0.00496011,0.00524354,0.00434600,0.00283435,0.00141717,0.00033067,0.00009448,0.00141717,0.00099202,0.00160613,0.00042515,-0.00037791,0.00018896,0.00085030,0.00278711,0.00462944,0.00543250,0.00647176,0.00618833,0.00633004,0.00647176,0.00746378,0.00878648,0.01025089,0.01100672,0.01029813,0.00826685,0.00500735,0.00151165,-0.00193680,-0.00444048,-0.00647176,-0.00680244,-0.00718035,-0.00590489,-0.00500735,-0.00359017,-0.00240920,-0.00184233,-0.00222024,-0.00344846,-0.00510183,-0.00684967,-0.00703863,-0.00585765,-0.00340122,-0.00037791,0.00236196,0.00396809,0.00377913,0.00264539,0.00023620,-0.00222024,-0.00316502,-0.00321226,-0.00179509,0.00028343,0.00151165,0.00330674,0.00458220,0.00722759,0.00968402,0.01166807,0.01105396,0.00760550,0.00085030,-0.00666072,-0.01369935,-0.01776191,-0.01743124,-0.01421898,-0.00769998,-0.00141717,0.00316502,0.00618833,0.00628280,0.00647176,0.00684967,0.00755826,0.00992022,0.01129015,0.01299076,0.01360487,0.01388831,0.01332144,0.01247113,0.01067604,0.00859752,0.00651900,0.00373189,0.00212576,0.00037791,0.00023620,0.00051963,0.00132270,0.00165337,0.00207852,0.00146441,0.00160613,0.00203128,0.00340122,0.00529078,0.00689691,0.00840857,0.00845581,0.00831409,0.00779446,0.00755826,0.00897544,0.01020365,0.01237665,0.01365211,0.01421898,0.01454965,0.01341591,0.01355763,0.01209322,0.01190426,0.01067604,0.00916439,0.00760550,0.00566870,0.00415704,0.00269263,0.00240920,0.00136993,0.00122822,0.00023620,-0.00056687,-0.00118098,-0.00132270,-0.00070859,-0.00042515,0.00066135,0.00061411,0.00155889,0.00146441,0.00179509,0.00160613,0.00132270,0.00118098,0.00151165,0.00160613,0.00174785,0.00066135,-0.00108650,-0.00311778,-0.00491287,-0.00486563,-0.00387361,-0.00103926,0.00198404,0.00462944,0.00623557,0.00637728,0.00491287,0.00363741,0.00089754,0.00023620,-0.00146441,-0.00056687,-0.00056687,0.00132270,0.00311778,0.00486563,0.00689691,0.00736931,0.00741654,0.00637728,0.00368465,0.00127546,-0.00292883,-0.00519630,-0.00703863,-0.00576317,-0.00321226,-0.00066135,-0.00061411,-0.00514907,-0.01275457,-0.02078522,-0.02328889,-0.01752572,-0.00250367,0.01577787,0.03061096,0.03524039,0.02631220,0.00892820,-0.01062881,-0.02461159,-0.02881587,-0.02513122,-0.01587235,-0.00718035,0.00066135,0.00481839,0.00732207,0.00722759,0.00477115,0.00132270,-0.00425152,-0.00769998,-0.01091224,-0.01058157,-0.00831409,-0.00472391,0.00089754,0.00581041,0.01010917,0.01105396,0.00892820,0.00222024,-0.00467667,-0.01171531,-0.01393554,-0.01176254,-0.00557422,0.00273987,0.00949507,0.01426622,0.01544720,0.01431346,0.01138463,0.00836133,0.00410980,0.00094478,-0.00340122,-0.00609385,-0.00878648,-0.01001470,-0.01001470,-0.01001470,-0.00888096,-0.00769998,-0.00642452,-0.00434600,-0.00316502,-0.00132270,-0.00113374,-0.00179509,-0.00453496,-0.00788894,-0.01039261,-0.00963678,-0.00396809,0.00429876,0.01355763,0.01809259,0.01762020,0.01171531,0.00448772,-0.00165337,-0.00429876,-0.00410980,-0.00321226,-0.00217300,-0.00264539,-0.00283435,-0.00363741,-0.00363741,-0.00307054,-0.00278711,-0.00108650,-0.00075583,0.00122822,0.00193680,0.00335398,0.00453496,0.00571594,0.00680244,0.00765274,0.00727483,0.00689691,0.00552698,0.00496011,0.00401533,0.00429876,0.00425152,0.00505459,0.00571594,0.00618833,0.00689691,0.00604661,0.00500735,0.00240920,-0.00061411,-0.00297607,-0.00486563,-0.00373189,-0.00278711,0.00037791,0.00009448,0.00037791,-0.00344846,-0.00585765,-0.00987298,-0.01129015,-0.01190426,-0.01124291,-0.00883372,-0.00699139,-0.00453496,-0.00401533,-0.00529078,-0.00821961,-0.01204598,-0.01403002,-0.01398278,-0.01006194,-0.00547974,-0.00047239,0.00174785,0.00122822,-0.00103926,-0.00410980,-0.00633004,-0.00651900,-0.00699139,-0.00590489,-0.00689691,-0.00727483,-0.00888096,-0.00992022,-0.01072328,-0.01152635,-0.01162083,-0.01266009,-0.01218770,-0.01232941,-0.01091224,-0.00963678,-0.00713311,-0.00557422,-0.00354294,-0.00302330,-0.00359017,-0.00472391,-0.00609385,-0.00699139,-0.00713311,-0.00642452,-0.00604661,-0.00538526,-0.00533802,-0.00566870,-0.00599937,-0.00633004,-0.00675520,-0.00680244,-0.00642452,-0.00581041,-0.00448772,-0.00321226,-0.00160613,0.00028343,0.00198404,0.00359017,0.00368465,0.00316502,0.00141717,0.00033067,-0.00080307,0.00094478,0.00222024,0.00510183,0.00661348,0.00684967,0.00661348,0.00444048,0.00311778,0.00004724,-0.00222024,-0.00566870,-0.00840857,-0.01086500,-0.01162083,-0.01176254,-0.00973126,-0.00798341,-0.00519630,-0.00340122,-0.00198404,-0.00113374,-0.00136993,-0.00132270,-0.00193680,-0.00198404,-0.00146441,-0.00094478,0.00070859,0.00155889,0.00297607,0.00297607,0.00330674,0.00273987,0.00198404,0.00113374,-0.00042515,-0.00179509,-0.00368465,-0.00557422,-0.00718035,-0.00859752,-0.00906991,-0.00935335,-0.00840857,-0.00736931,-0.00543250,-0.00382637,-0.00184233,-0.00113374,0.00033067,-0.00009448,0.00080307,0.00070859,0.00089754,0.00080307,-0.00033067,-0.00184233,-0.00382637,-0.00566870,-0.00666072,-0.00666072,-0.00590489,-0.00444048,-0.00307054,-0.00245644,-0.00174785,-0.00207852,-0.00193680,-0.00245644,-0.00250367,-0.00264539,-0.00217300,-0.00103926,0.00061411,0.00184233,0.00335398,0.00288159,0.00127546,-0.00160613,-0.00633004,-0.00973126,-0.01228218,-0.01166807,-0.00798341,-0.00377913,0.00174785,0.00321226,0.00472391,0.00188957,0.00094478,-0.00165337,-0.00231472,-0.00425152,-0.00571594,-0.00855028,-0.00963678,-0.01053433,-0.00916439,-0.00732207,-0.00434600,-0.00217300,0.00118098,0.00273987,0.00562146,0.00666072,0.00812513,0.00831409,0.00746378,0.00604661,0.00344846,0.00184233,0.00028343,0.00070859,0.00179509,0.00316502,0.00538526,0.00661348,0.00807789,0.00873924,0.00831409,0.00694415,0.00434600,0.00231472,0.00141717,0.00207852,0.00429876,0.00633004,0.00732207,0.00769998,0.00604661,0.00524354,0.00368465,0.00316502,0.00269263,0.00273987,0.00302330,0.00354294,0.00425152,0.00448772,0.00415704,0.00359017,0.00188957,0.00056687,-0.00066135,-0.00136993,-0.00103926,-0.00042515,0.00066135,0.00179509,0.00184233,0.00151165,-0.00033067,-0.00240920,-0.00420428,-0.00576317,-0.00557422,-0.00429876,-0.00222024,0.00080307,0.00264539,0.00382637,0.00349570,0.00273987,0.00184233,0.00132270,0.00127546,0.00056687,-0.00033067,-0.00222024,-0.00373189,-0.00439324,-0.00377913,-0.00165337,0.00018896,0.00222024,0.00292883,0.00344846,0.00377913,0.00359017,0.00316502,0.00240920,0.00056687,-0.00056687,-0.00226748,-0.00255091,-0.00269263,-0.00132270,-0.00127546,0.00014172,-0.00075583,-0.00132270,-0.00255091,-0.00514907,-0.00675520,-0.00892820,-0.01010917,-0.00958954,-0.00821961,-0.00604661,-0.00302330,-0.00165337,0.00056687,0.00118098,0.00307054,0.00496011,0.00703863,0.00897544,0.00864476,0.00850304,0.00576317,0.00387361,0.00170061,-0.00075583,-0.00136993,-0.00368465,-0.00382637,-0.00472391,-0.00415704,-0.00330674,-0.00198404,-0.00094478,-0.00099202,-0.00056687,-0.00212576,-0.00170061,-0.00273987,-0.00255091,-0.00325950,-0.00458220,-0.00623557,-0.00836133,-0.00958954,-0.01043985,-0.01015641,-0.00878648,-0.00732207,-0.00486563,-0.00368465,-0.00170061,-0.00174785,-0.00085030,-0.00146441,-0.00198404,-0.00259815,-0.00377913,-0.00377913,-0.00401533,-0.00245644,-0.00141717,0.00089754,0.00212576,0.00373189,0.00387361,0.00340122,0.00127546,-0.00170061,-0.00576317,-0.00897544,-0.01157359,-0.01237665,-0.01133739,-0.00944783,-0.00633004,-0.00387361,-0.00127546,0.00023620,0.00108650,0.00179509,0.00174785,0.00273987,0.00226748,0.00250367,0.00085030,0.00009448,-0.00141717,-0.00231472,-0.00236196,-0.00292883,-0.00198404,-0.00222024,-0.00089754,-0.00080307,0.00014172,-0.00014172,-0.00028343,-0.00075583,-0.00122822,-0.00085030,-0.00056687,0.00099202,0.00165337,0.00273987,0.00255091,0.00236196,0.00089754,-0.00056687,-0.00349570,-0.00571594,-0.00916439,-0.01039261,-0.01152635,-0.01053433,-0.00925887,-0.00812513,-0.00708587,-0.00746378,-0.00727483,-0.00803065,-0.00803065,-0.00855028,-0.00859752,-0.00897544,-0.00878648,-0.00821961,-0.00760550,-0.00609385,-0.00491287,-0.00288159,-0.00155889,-0.00132270,-0.00231472,-0.00514907,-0.00741654,-0.00987298,-0.00940059,-0.00845581,-0.00562146,-0.00278711,-0.00037791,0.00212576,0.00316502,0.00382637,0.00311778,0.00193680,-0.00028343,-0.00222024,-0.00500735,-0.00694415,-0.00888096,-0.01010917,-0.00987298,-0.00821961,-0.00581041,-0.00259815,-0.00037791,0.00207852,0.00283435,0.00354294,0.00302330,0.00250367,0.00259815,0.00184233,0.00226748,0.00193680,0.00122822,0.00018896,-0.00222024,-0.00434600,-0.00718035,-0.00821961,-0.00963678,-0.00817237,-0.00675520,-0.00425152,-0.00146441,-0.00009448,0.00170061,0.00179509,0.00212576,0.00188957,0.00188957,0.00151165,0.00184233,0.00099202,0.00113374,0.00042515,0.00080307,0.00085030,0.00160613,0.00193680,0.00188957,0.00188957,0.00018896,-0.00070859,-0.00377913,-0.00514907,-0.00774722,-0.00760550,-0.00751102,-0.00571594,-0.00481839,-0.00349570,-0.00368465,-0.00311778,-0.00278711,-0.00165337,-0.00075583,0.00113374,0.00193680,0.00396809,0.00472391,0.00562146,0.00481839,0.00373189,0.00108650,-0.00004724,-0.00146441,-0.00094478,-0.00018896,0.00028343,0.00070859,-0.00108650,-0.00217300,-0.00481839,-0.00547974,-0.00628280,-0.00533802,-0.00387361,-0.00226748,-0.00028343,0.00023620,0.00070859,-0.00033067,-0.00255091,-0.00406257,-0.00661348,-0.00694415,-0.00765274,-0.00803065,-0.00751102,-0.00755826,-0.00581041,-0.00382637,-0.00212576,-0.00089754,-0.00151165,-0.00302330,-0.00439324,-0.00571594,-0.00576317,-0.00642452,-0.00623557,-0.00604661,-0.00505459,-0.00240920,-0.00070859,0.00222024,0.00203128,0.00141717,-0.00051963,-0.00226748,-0.00373189,-0.00406257,-0.00472391,-0.00491287,-0.00514907,-0.00595213,-0.00576317,-0.00562146,-0.00462944,-0.00226748,-0.00113374,0.00146441,0.00222024,0.00330674,0.00278711,0.00188957,-0.00018896,-0.00259815,-0.00481839,-0.00647176,-0.00661348,-0.00557422,-0.00382637,-0.00222024,-0.00203128,-0.00217300,-0.00349570,-0.00382637,-0.00321226,-0.00226748,0.00004724,0.00240920,0.00406257,0.00656624,0.00803065,0.00963678,0.01086500,0.01124291,0.01081776,0.01081776,0.00973126,0.00902267,0.00708587,0.00410980,0.00037791,-0.00269263,-0.00439324,-0.00330674,0.00051963,0.00505459,0.01077052,0.01379383,0.01639198,0.01591959,0.01421898,0.01152635,0.00746378,0.00524354,0.00160613,0.00085030,-0.00094478,-0.00028343,0.00000000,0.00212576,0.00340122,0.00467667,0.00481839,0.00387361,0.00307054,0.00236196,0.00226748,0.00250367,0.00273987,0.00236196,0.00231472,0.00174785,0.00179509,0.00184233,0.00222024,0.00273987,0.00359017,0.00481839,0.00628280,0.00751102,0.00741654,0.00680244,0.00462944,0.00354294,0.00170061,0.00108650,0.00018896,-0.00075583,-0.00165337,-0.00193680,-0.00141717,-0.00070859,0.00014172,-0.00075583,-0.00193680,-0.00415704,-0.00595213,-0.00727483,-0.00661348,-0.00566870,-0.00288159,-0.00066135,0.00259815,0.00392085,0.00595213,0.00571594,0.00566870,0.00472391,0.00368465,0.00269263,0.00198404,0.00160613,0.00193680,0.00226748,0.00259815,0.00236196,0.00151165,-0.00037791,-0.00170061,-0.00392085,-0.00439324,-0.00462944,-0.00321226,-0.00207852,-0.00056687,-0.00023620,-0.00037791,-0.00066135,-0.00132270,-0.00136993,-0.00170061,-0.00165337,-0.00160613,-0.00127546,-0.00085030,-0.00108650,-0.00094478,-0.00212576,-0.00207852,-0.00231472,-0.00207852,-0.00193680,-0.00359017,-0.00651900,-0.00963678,-0.01289628,-0.01355763,-0.01322696,-0.01232941,-0.01119567,-0.01067604,-0.00973126,-0.00821961,-0.00552698,-0.00373189,-0.00108650,-0.00132270,-0.00070859,-0.00255091,-0.00321226,-0.00462944,-0.00425152,-0.00330674,0.00000000,0.00420428,0.00940059,0.01502204,0.01856498,0.02111589,0.01955700,0.01658094,0.01034537,0.00382637,-0.00264539,-0.00713311,-0.01048709,-0.01152635,-0.01313248,-0.01403002,-0.01506928,-0.01497481,-0.01355763,-0.01053433,-0.00765274,-0.00481839,-0.00368465,-0.00396809,-0.00496011,-0.00623557,-0.00651900,-0.00713311,-0.00637728,-0.00666072,-0.00571594,-0.00481839,-0.00292883,-0.00061411,0.00236196,0.00444048,0.00633004,0.00684967,0.00821961,0.00968402,0.01190426,0.01365211,0.01303800,0.01010917,0.00467667,-0.00023620,-0.00340122,-0.00288159,0.00099202,0.00552698,0.01100672,0.01403002,0.01662818,0.01667541,0.01558891,0.01147911,0.00633004,-0.00122822,-0.00656624,-0.01100672,-0.01086500,-0.00873924,-0.00396809,0.00118098,0.00543250,0.00732207,0.00599937,0.00160613,-0.00420428,-0.01062881,-0.01445518,-0.01568339,-0.01365211,-0.00949507,-0.00566870,-0.00217300,-0.00165337,-0.00160613,-0.00387361,-0.00496011,-0.00699139,-0.00803065,-0.00817237,-0.00807789,-0.00604661,-0.00533802,-0.00354294,-0.00321226,-0.00222024,-0.00108650,0.00009448,0.00217300,0.00302330,0.00467667,0.00467667,0.00590489,0.00566870,0.00486563,0.00316502,-0.00075583,-0.00448772,-0.00732207,-0.01077052,-0.01081776,-0.01228218,-0.00958954,-0.00604661,0.00075583,0.00708587,0.01086500,0.00982574,0.00415704,-0.00344846,-0.00944783,-0.01195150,-0.01129015,-0.00689691,-0.00316502,0.00278711,0.00727483,0.01209322,0.01445518,0.01469137,0.01077052,0.00524354,-0.00184233,-0.00864476,-0.01332144,-0.01558891,-0.01426622,-0.01025089,-0.00439324,0.00066135,0.00514907,0.00557422,0.00524354,0.00255091,0.00122822,0.00127546,0.00250367,0.00500735,0.00798341,0.01010917,0.01199874,0.01199874,0.01091224,0.00968402,0.00755826,0.00680244,0.00590489,0.00552698,0.00500735,0.00420428,0.00321226,0.00259815,0.00193680,0.00099202,-0.00066135,-0.00387361,-0.00666072,-0.00935335,-0.00958954,-0.00883372,-0.00642452,-0.00396809,-0.00113374,0.00245644,0.00519630,0.00916439,0.00958954,0.01015641,0.00755826,0.00604661,0.00547974,0.00552698,0.00751102,0.00708587,0.00722759,0.00500735,0.00302330,0.00056687,-0.00170061,-0.00363741,-0.00467667,-0.00571594,-0.00444048,-0.00486563,-0.00297607,-0.00226748,0.00004724,0.00297607,0.00651900,0.00944783,0.01218770,0.01209322,0.01247113,0.01062881,0.00958954,0.00949507,0.00968402,0.01214046,0.01403002,0.01535272,0.01601407,0.01445518,0.01256561,0.01062881,0.00855028,0.00798341,0.00727483,0.00779446,0.00798341,0.00916439,0.00968402,0.01124291,0.01152635,0.01256561,0.01313248,0.01317972,0.01332144,0.01214046,0.01081776,0.00935335,0.00746378,0.00618833,0.00510183,0.00472391,0.00519630,0.00656624,0.00774722,0.00873924,0.00845581,0.00755826,0.00666072,0.00529078,0.00562146,0.00472391,0.00519630,0.00462944,0.00396809,0.00297607,0.00099202,0.00014172,-0.00089754,0.00028343,0.00155889,0.00410980,0.00444048,0.00496011,0.00217300,0.00099202,-0.00160613,-0.00231472,-0.00255091,-0.00255091,-0.00118098,-0.00042515,0.00127546,0.00231472,0.00302330,0.00311778,0.00330674,0.00255091,0.00259815,0.00099202,0.00028343,-0.00033067,-0.00061411,0.00056687,0.00051963,0.00056687,-0.00099202,-0.00288159,-0.00448772,-0.00623557,-0.00623557,-0.00666072,-0.00581041,-0.00514907,-0.00410980,-0.00278711,-0.00108650,0.00033067,0.00165337,0.00278711,0.00325950,0.00349570,0.00349570,0.00273987,0.00222024,0.00151165,0.00113374,0.00155889,0.00344846,0.00467667,0.00562146,0.00321226,-0.00080307,-0.00618833,-0.00878648,-0.00883372,-0.00510183,-0.00051963,0.00273987,0.00505459,0.00566870,0.00736931,0.00921163,0.01095948,0.01077052,0.00836133,0.00387361,-0.00080307,-0.00519630,-0.00793617,-0.00925887,-0.00940059,-0.00864476,-0.00736931,-0.00576317,-0.00500735,-0.00477115,-0.00458220,-0.00510183,-0.00392085,-0.00321226,-0.00122822,0.00066135,0.00174785,0.00264539,0.00212576,0.00179509,0.00132270,0.00226748,0.00363741,0.00623557,0.00826685,0.00977850,0.01157359,0.01195150,0.01360487,0.01303800,0.01214046,0.01020365,0.00732207,0.00529078,0.00245644,0.00141717,0.00037791,0.00170061,0.00344846,0.00609385,0.00803065,0.00869200,0.00826685,0.00623557,0.00396809,0.00070859,-0.00226748,-0.00462944,-0.00514907,-0.00410980,-0.00155889,0.00047239,0.00184233,0.00297607,0.00368465,0.00623557,0.00817237,0.00992022,0.00925887,0.00741654,0.00599937,0.00486563,0.00614109,0.00628280,0.00604661,0.00491287,0.00288159,0.00255091,0.00236196,0.00316502,0.00321226,0.00269263,0.00179509,0.00042515,-0.00136993,-0.00222024,-0.00278711,-0.00122822,0.00179509,0.00410980,0.00618833,0.00448772,0.00222024,-0.00118098,-0.00259815,-0.00203128,-0.00037791,0.00226748,0.00335398,0.00363741,0.00188957,-0.00080307,-0.00387361,-0.00699139,-0.00784170,-0.00831409,-0.00623557,-0.00401533,-0.00122822,0.00174785,0.00396809,0.00651900,0.00732207,0.00845581,0.00722759,0.00595213,0.00240920,-0.00170061,-0.00595213,-0.00987298,-0.01029813,-0.00888096,-0.00377913,0.00179509,0.00557422,0.00703863,0.00505459,0.00155889,-0.00188957,-0.00505459,-0.00694415,-0.00888096,-0.00973126,-0.01067604,-0.00935335,-0.00788894,-0.00359017,-0.00023620,0.00340122,0.00562146,0.00562146,0.00533802,0.00292883,0.00141717,-0.00056687,-0.00089754,-0.00118098,0.00061411,0.00108650,0.00311778,0.00269263,0.00302330,0.00160613,0.00094478,0.00000000,0.00018896,0.00103926,0.00264539,0.00477115,0.00675520,0.00769998,0.00760550,0.00599937,0.00330674,0.00103926,-0.00155889,-0.00217300,-0.00259815,-0.00184233,-0.00051963,0.00047239,0.00297607,0.00307054,0.00514907,0.00396809,0.00486563,0.00429876,0.00500735,0.00590489,0.00651900,0.00694415,0.00633004,0.00481839,0.00368465,0.00212576,0.00231472,0.00269263,0.00425152,0.00552698,0.00618833,0.00633004,0.00500735,0.00335398,0.00146441,-0.00085030,-0.00217300,-0.00321226,-0.00302330,-0.00188957,0.00028343,0.00264539,0.00524354,0.00684967,0.00779446,0.00708587,0.00599937,0.00382637,0.00240920,0.00056687,0.00080307,-0.00037791,0.00066135,0.00023620,0.00118098,0.00170061,0.00264539,0.00236196,0.00165337,-0.00004724,-0.00203128,-0.00288159,-0.00297607,-0.00174785,0.00061411,0.00165337,0.00292883,0.00226748,0.00160613,0.00099202,0.00009448,-0.00033067,-0.00103926,-0.00245644,-0.00307054,-0.00387361,-0.00316502,-0.00198404,0.00000000,0.00099202,0.00174785,0.00108650,0.00014172,-0.00023620,-0.00089754,0.00023620,0.00042515,0.00236196,0.00288159,0.00519630,0.00614109,0.00722759,0.00647176,0.00481839,0.00165337,-0.00165337,-0.00387361,-0.00486563,-0.00335398,-0.00051963,0.00255091,0.00562146,0.00699139,0.00769998,0.00722759,0.00647176,0.00552698,0.00453496,0.00335398,0.00231472,0.00113374,0.00070859,0.00018896,0.00085030,0.00047239,0.00080307,0.00051963,-0.00042515,-0.00193680,-0.00448772,-0.00727483,-0.00968402,-0.01081776,-0.01010917,-0.00727483,-0.00321226,0.00099202,0.00477115,0.00727483,0.00906991,0.00921163,0.00930611,0.00788894,0.00675520,0.00562146,0.00425152,0.00406257,0.00307054,0.00316502,0.00316502,0.00340122,0.00448772,0.00524354,0.00628280,0.00675520,0.00718035,0.00684967,0.00751102,0.00699139,0.00722759,0.00609385,0.00472391,0.00288159,0.00174785,0.00014172,-0.00004724,-0.00179509,-0.00273987,-0.00500735,-0.00661348,-0.00798341,-0.00869200,-0.00774722,-0.00680244,-0.00453496,-0.00269263,-0.00118098,0.00018896,0.00023620,0.00118098,0.00113374,0.00155889,0.00193680,0.00184233,0.00240920,0.00231472,0.00297607,0.00283435,0.00259815,0.00170061,0.00028343,-0.00094478,-0.00141717,-0.00165337,-0.00066135,-0.00042515,0.00037791,0.00066135,0.00108650,0.00094478,0.00018896,-0.00099202,-0.00292883,-0.00415704,-0.00448772,-0.00410980,-0.00198404,-0.00009448,0.00174785,0.00311778,0.00259815,0.00240920,0.00103926,0.00042515,-0.00051963,-0.00070859,-0.00160613,-0.00188957,-0.00297607,-0.00335398,-0.00330674,-0.00259815,-0.00132270,-0.00033067,0.00108650,0.00103926,0.00217300,0.00151165,0.00184233,0.00099202,-0.00037791,-0.00273987,-0.00510183,-0.00821961,-0.00968402,-0.00963678,-0.00850304,-0.00486563,-0.00236196,0.00118098,0.00222024,0.00321226,0.00278711,0.00212576,0.00113374,0.00047239,-0.00085030,-0.00127546,-0.00250367,-0.00250367,-0.00349570,-0.00344846,-0.00439324,-0.00491287,-0.00529078,-0.00500735,-0.00486563,-0.00311778,-0.00245644,-0.00047239,-0.00047239,-0.00009448,-0.00222024,-0.00316502,-0.00609385,-0.00651900,-0.00684967,-0.00604661,-0.00401533,-0.00302330,-0.00207852,-0.00165337,-0.00231472,-0.00245644,-0.00269263,-0.00136993,-0.00089754,0.00141717,0.00061411,0.00118098,-0.00051963,-0.00113374,-0.00099202,-0.00070859,0.00075583,0.00108650,0.00165337,0.00170061,0.00226748,0.00250367,0.00264539,0.00226748,0.00056687,-0.00146441,-0.00283435,-0.00472391,-0.00467667,-0.00496011,-0.00429876,-0.00273987,-0.00122822,0.00018896,0.00184233,0.00203128,0.00250367,0.00222024,0.00151165,0.00103926,0.00000000,-0.00085030,-0.00165337,-0.00236196,-0.00278711,-0.00311778,-0.00410980,-0.00444048,-0.00543250,-0.00510183,-0.00496011,-0.00425152,-0.00292883,-0.00188957,-0.00009448,0.00127546,0.00250367,0.00316502,0.00278711,0.00203128,0.00085030,0.00018896,-0.00056687,-0.00033067,-0.00014172,0.00023620,0.00108650,0.00118098,0.00136993,0.00047239,-0.00089754,-0.00311778,-0.00557422,-0.00703863,-0.00755826,-0.00656624,-0.00420428,-0.00273987,-0.00028343,-0.00033067,0.00009448,-0.00085030,-0.00141717,-0.00226748,-0.00283435,-0.00420428,-0.00477115,-0.00618833,-0.00670796,-0.00670796,-0.00618833,-0.00510183,-0.00396809,-0.00344846,-0.00297607,-0.00359017,-0.00382637,-0.00519630,-0.00566870,-0.00562146,-0.00505459,-0.00340122,-0.00212576,-0.00170061,-0.00089754,-0.00193680,-0.00212576,-0.00307054,-0.00420428,-0.00543250,-0.00718035,-0.00888096,-0.00925887,-0.00892820,-0.00642452,-0.00387361,-0.00028343,0.00226748,0.00410980,0.00510183,0.00439324,0.00377913,0.00264539,0.00151165,0.00113374,-0.00037791,-0.00113374,-0.00273987,-0.00354294,-0.00354294,-0.00344846,-0.00203128,-0.00151165,-0.00080307,-0.00118098,-0.00118098,-0.00198404,-0.00198404,-0.00184233,-0.00236196,-0.00165337,-0.00264539,-0.00212576,-0.00250367,-0.00198404,-0.00132270,-0.00170061,-0.00160613,-0.00316502,-0.00325950,-0.00359017,-0.00132270,0.00018896,0.00226748,0.00146441,-0.00085030,-0.00439324,-0.00817237,-0.00992022,-0.01086500,-0.01020365,-0.00940059,-0.00850304,-0.00722759,-0.00562146,-0.00368465,-0.00174785,-0.00066135,0.00033067,0.00023620,-0.00009448,0.00047239,-0.00014172,0.00085030,0.00023620,0.00037791,-0.00099202,-0.00136993,-0.00283435,-0.00259815,-0.00335398,-0.00231472,-0.00236196,-0.00151165,-0.00085030,-0.00018896,0.00075583,0.00132270,0.00188957,0.00198404,0.00222024,0.00160613,0.00146441,0.00099202,0.00141717,0.00236196,0.00429876,0.00566870,0.00637728,0.00472391,0.00132270,-0.00269263,-0.00722759,-0.00859752,-0.00878648,-0.00533802,-0.00037791,0.00557422,0.01015641,0.01379383,0.01294352,0.01119567,0.00618833,0.00198404,-0.00203128,-0.00491287,-0.00618833,-0.00708587,-0.00703863,-0.00656624,-0.00557422,-0.00354294,-0.00212576,-0.00023620,-0.00075583,-0.00151165,-0.00429876,-0.00656624,-0.00788894,-0.00722759,-0.00500735,-0.00151165,0.00160613,0.00406257,0.00566870,0.00633004,0.00680244,0.00647176,0.00562146,0.00373189,0.00188957,-0.00042515,-0.00188957,-0.00316502,-0.00325950,-0.00288159,-0.00179509,0.00018896,0.00155889,0.00396809,0.00410980,0.00538526,0.00448772,0.00472391,0.00458220,0.00458220,0.00557422,0.00557422,0.00623557,0.00581041,0.00538526,0.00406257,0.00278711,0.00122822,0.00018896,-0.00141717,-0.00188957,-0.00396809,-0.00377913,-0.00491287,-0.00340122,-0.00250367,-0.00042515,0.00085030,0.00155889,0.00132270,0.00118098,0.00009448,0.00009448,-0.00089754,-0.00132270,-0.00217300,-0.00278711,-0.00401533,-0.00439324,-0.00566870,-0.00651900,-0.00713311,-0.00812513,-0.00727483,-0.00722759,-0.00496011,-0.00406257,-0.00236196,-0.00212576,-0.00231472,-0.00255091,-0.00311778,-0.00316502,-0.00340122,-0.00373189,-0.00462944,-0.00595213,-0.00708587,-0.00817237,-0.00774722,-0.00755826,-0.00609385,-0.00529078,-0.00406257,-0.00344846,-0.00311778,-0.00307054,-0.00311778,-0.00240920,-0.00132270,0.00099202,0.00335398,0.00595213,0.00736931,0.00836133,0.00779446,0.00727483,0.00529078,0.00335398,0.00094478,-0.00085030,-0.00155889,-0.00198404,-0.00212576,-0.00259815,-0.00396809,-0.00491287,-0.00505459,-0.00420428,-0.00122822,0.00118098,0.00552698,0.00718035,0.01062881,0.01015641,0.01029813,0.00727483,0.00401533,-0.00023620,-0.00392085,-0.00656624,-0.00845581,-0.00892820,-0.00845581,-0.00713311,-0.00486563,-0.00184233,0.00080307,0.00396809,0.00590489,0.00769998,0.00850304,0.00949507,0.00873924,0.00925887,0.00736931,0.00604661,0.00307054,0.00033067,-0.00212576,-0.00307054,-0.00255091,0.00014172,0.00297607,0.00623557,0.00831409,0.00954231,0.01067604,0.01072328,0.01034537,0.00954231,0.00675520,0.00396809,0.00056687,-0.00198404,-0.00359017,-0.00330674,-0.00311778,-0.00099202,-0.00023620,0.00160613,0.00245644,0.00316502,0.00368465,0.00288159,0.00203128,0.00014172,-0.00217300,-0.00363741,-0.00481839,-0.00377913,-0.00250367,0.00042515,0.00118098,0.00212576,-0.00047239,-0.00307054,-0.00703863,-0.00911715,-0.01034537,-0.00850304,-0.00576317,-0.00094478,0.00325950,0.00680244,0.00855028,0.00793617,0.00510183,0.00070859,-0.00415704,-0.00831409,-0.01015641,-0.01081776,-0.00840857,-0.00585765,-0.00184233,0.00108650,0.00401533,0.00562146,0.00670796,0.00718035,0.00651900,0.00595213,0.00434600,0.00307054,0.00160613,0.00103926,0.00042515,0.00080307,0.00170061,0.00188957,0.00307054,0.00255091,0.00259815,0.00113374,0.00004724,-0.00259815,-0.00444048,-0.00651900,-0.00784170,-0.00798341,-0.00774722,-0.00623557,-0.00458220,-0.00264539,-0.00103926,0.00000000,0.00085030,0.00070859,0.00075583,-0.00094478,-0.00170061,-0.00406257,-0.00581041,-0.00855028,-0.01086500,-0.01332144,-0.01558891,-0.01634474,-0.01710057,-0.01502204,-0.01294352,-0.00892820,-0.00538526,-0.00231472,0.00000000,0.00033067,0.00023620,-0.00103926,-0.00222024,-0.00321226,-0.00382637,-0.00387361,-0.00410980,-0.00406257,-0.00340122,-0.00373189,-0.00226748,-0.00335398,-0.00283435,-0.00496011,-0.00614109,-0.00831409,-0.00954231,-0.00982574,-0.00892820,-0.00732207,-0.00448772,-0.00231472,-0.00014172,0.00122822,0.00174785,0.00146441,0.00179509,0.00113374,0.00184233,0.00179509,0.00203128,0.00174785,0.00146441,0.00070859,-0.00047239,-0.00136993,-0.00259815,-0.00321226,-0.00278711,-0.00212576,-0.00028343,0.00089754,0.00198404,0.00170061,0.00089754,-0.00122822,-0.00363741,-0.00604661,-0.00788894,-0.00836133,-0.00831409,-0.00656624,-0.00533802,-0.00311778,-0.00146441,-0.00066135,0.00037791,-0.00037791,-0.00061411,-0.00207852,-0.00283435,-0.00406257,-0.00401533,-0.00396809,-0.00250367,0.00051963,0.00278711,0.00689691,0.00751102,0.00831409,0.00614109,0.00420428,0.00089754,-0.00113374,-0.00349570,-0.00415704,-0.00396809,-0.00240920,-0.00014172,0.00170061,0.00250367,0.00259815,0.00179509,0.00141717,0.00165337,0.00193680,0.00269263,0.00278711,0.00307054,0.00283435,0.00269263,0.00146441,-0.00037791,-0.00292883,-0.00566870,-0.00666072,-0.00826685,-0.00694415,-0.00666072,-0.00439324,-0.00297607,-0.00184233,-0.00146441,-0.00240920,-0.00316502,-0.00377913,-0.00325950,-0.00245644,-0.00174785,-0.00259815,-0.00382637,-0.00590489,-0.00718035,-0.00751102,-0.00684967,-0.00467667,-0.00203128,0.00231472,0.00590489,0.00954231,0.01143187,0.01110120,0.01010917,0.00751102,0.00529078,0.00307054,0.00108650,-0.00033067,-0.00174785,-0.00141717,-0.00184233,0.00014172,0.00099202,0.00250367,0.00429876,0.00453496,0.00562146,0.00439324,0.00401533,0.00212576,0.00141717,0.00023620,-0.00004724,0.00047239,0.00136993,0.00316502,0.00481839,0.00628280,0.00689691,0.00656624,0.00444048,0.00297607,-0.00042515,-0.00132270,-0.00255091,-0.00278711,-0.00193680,-0.00207852,-0.00132270,-0.00103926,0.00004724,0.00099202,0.00255091,0.00340122,0.00354294,0.00425152,0.00368465,0.00434600,0.00387361,0.00307054,0.00240920,0.00136993,0.00179509,0.00240920,0.00401533,0.00448772,0.00524354,0.00500735,0.00510183,0.00604661,0.00656624,0.00727483,0.00732207,0.00633004,0.00519630,0.00359017,0.00283435,0.00245644,0.00269263,0.00325950,0.00311778,0.00259815,0.00146441,-0.00085030,-0.00184233,-0.00354294,-0.00316502,-0.00236196,-0.00080307,0.00198404,0.00392085,0.00623557,0.00680244,0.00618833,0.00368465,0.00160613,-0.00179509,-0.00273987,-0.00439324,-0.00462944,-0.00533802,-0.00576317,-0.00566870,-0.00500735,-0.00373189,-0.00165337,-0.00009448,0.00193680,0.00245644,0.00349570,0.00302330,0.00392085,0.00420428,0.00519630,0.00642452,0.00708587,0.00812513,0.00779446,0.00727483,0.00519630,0.00311778,0.00094478,-0.00089754,-0.00075583,-0.00094478,0.00155889,0.00278711,0.00448772,0.00538526,0.00500735,0.00496011,0.00462944,0.00448772,0.00524354,0.00590489,0.00684967,0.00755826,0.00718035,0.00666072,0.00543250,0.00486563,0.00396809,0.00410980,0.00420428,0.00491287,0.00571594,0.00581041,0.00581041,0.00472391,0.00368465,0.00193680,0.00056687,-0.00151165,-0.00278711,-0.00439324,-0.00538526,-0.00566870,-0.00604661,-0.00576317,-0.00552698,-0.00538526,-0.00595213,-0.00628280,-0.00803065,-0.00897544,-0.01029813,-0.00987298,-0.00869200,-0.00500735,-0.00146441,0.00222024,0.00458220,0.00434600,0.00354294,0.00094478,-0.00089754,-0.00236196,-0.00321226,-0.00278711,-0.00288159,-0.00198404,-0.00198404,-0.00170061,-0.00222024,-0.00231472,-0.00368465,-0.00373189,-0.00410980,-0.00316502,-0.00099202,0.00099202,0.00415704,0.00566870,0.00727483,0.00736931,0.00708587,0.00552698,0.00406257,0.00165337,0.00108650,0.00094478,0.00236196,0.00439324,0.00590489,0.00642452,0.00604661,0.00458220,0.00330674,0.00226748,0.00122822,0.00094478,0.00023620,-0.00023620,-0.00108650,-0.00245644,-0.00453496,-0.00755826,-0.01025089,-0.01294352,-0.01303800,-0.01251837,-0.00850304,-0.00467667,0.00051963,0.00467667,0.00718035,0.00906991,0.00859752,0.00736931,0.00496011,0.00184233,-0.00118098,-0.00259815,-0.00396809,-0.00222024,-0.00099202,0.00089754,0.00245644,0.00188957,0.00155889,-0.00037791,-0.00127546,-0.00273987,-0.00311778,-0.00377913,-0.00392085,-0.00335398,-0.00316502,-0.00207852,-0.00127546,0.00004724,0.00094478,0.00264539,0.00307054,0.00453496,0.00491287,0.00500735,0.00519630,0.00458220,0.00321226,0.00188957,-0.00141717,-0.00363741,-0.00722759,-0.00883372,-0.01039261,-0.01010917,-0.00968402,-0.00774722,-0.00628280,-0.00354294,-0.00160613,0.00061411,0.00217300,0.00297607,0.00288159,0.00259815,0.00160613,0.00103926,0.00080307,0.00085030,0.00122822,0.00198404,0.00207852,0.00245644,0.00240920,0.00269263,0.00344846,0.00420428,0.00576317,0.00670796,0.00774722,0.00803065,0.00736931,0.00618833,0.00420428,0.00222024,0.00028343,-0.00113374,-0.00151165,-0.00165337,-0.00085030,-0.00075583,0.00023620,-0.00042515,-0.00028343,-0.00118098,-0.00165337,-0.00174785,-0.00222024,-0.00240920,-0.00283435,-0.00387361,-0.00382637,-0.00410980,-0.00349570,-0.00255091,-0.00264539,-0.00273987,-0.00453496,-0.00562146,-0.00807789,-0.00836133,-0.00992022,-0.00921163,-0.00850304,-0.00746378,-0.00538526,-0.00382637,-0.00174785,0.00080307,0.00316502,0.00576317,0.00826685,0.00855028,0.00845581,0.00562146,0.00250367,-0.00132270,-0.00382637,-0.00566870,-0.00571594,-0.00477115,-0.00425152,-0.00335398,-0.00377913,-0.00377913,-0.00401533,-0.00330674,-0.00273987,-0.00184233,-0.00141717,-0.00146441,-0.00146441,-0.00122822,-0.00160613,-0.00188957,-0.00269263,-0.00448772,-0.00552698,-0.00703863,-0.00784170,-0.00850304,-0.00916439,-0.00958954,-0.00973126,-0.00954231,-0.00906991,-0.00930611,-0.00992022,-0.01100672,-0.01261285,-0.01308524,-0.01299076,-0.01185702,-0.00911715,-0.00666072,-0.00321226,-0.00080307,0.00151165,0.00264539,0.00297607,0.00245644,0.00136993,-0.00033067,-0.00212576,-0.00425152,-0.00566870,-0.00675520,-0.00642452,-0.00614109,-0.00467667,-0.00396809,-0.00269263,-0.00193680,-0.00075583,0.00047239,0.00099202,0.00188957,0.00075583,0.00108650,-0.00080307,-0.00033067,-0.00151165,-0.00118098,-0.00188957,-0.00207852,-0.00321226,-0.00368465,-0.00543250,-0.00642452,-0.00826685,-0.00902267,-0.00859752,-0.00675520,-0.00373189,0.00037791,0.00273987,0.00439324,0.00335398,0.00103926,-0.00203128,-0.00519630,-0.00708587,-0.00812513,-0.00751102,-0.00647176,-0.00486563,-0.00231472,-0.00061411,0.00127546,0.00184233,0.00198404,0.00113374,0.00127546,0.00033067,0.00061411,0.00037791,0.00009448,0.00061411,0.00080307,0.00136993,0.00240920,0.00240920,0.00307054,0.00283435,0.00217300,0.00132270,-0.00075583,-0.00269263,-0.00496011,-0.00538526,-0.00481839,-0.00240920,-0.00018896,0.00170061,0.00236196,0.00146441,-0.00028343,-0.00250367,-0.00486563,-0.00642452,-0.00769998,-0.00817237,-0.00769998,-0.00661348,-0.00500735,-0.00392085,-0.00321226,-0.00396809,-0.00453496,-0.00505459,-0.00401533,-0.00207852,0.00075583,0.00222024,0.00273987,0.00070859,-0.00146441,-0.00311778,-0.00458220,-0.00335398,-0.00307054,-0.00141717,0.00023620,0.00118098,0.00278711,0.00292883,0.00292883,0.00066135,-0.00132270,-0.00477115,-0.00642452,-0.00751102,-0.00623557,-0.00377913,-0.00113374,0.00094478,0.00075583,-0.00047239,-0.00264539,-0.00444048,-0.00543250,-0.00519630,-0.00524354,-0.00373189,-0.00344846,-0.00179509,-0.00141717,-0.00155889,-0.00151165,-0.00184233,-0.00033067,0.00151165,0.00311778,0.00448772,0.00401533,0.00453496,0.00519630,0.00708587,0.00888096,0.00831409,0.00590489,0.00089754,-0.00283435,-0.00576317,-0.00448772,-0.00273987,0.00094478,0.00354294,0.00552698,0.00666072,0.00765274,0.00732207,0.00812513,0.00642452,0.00599937,0.00325950,0.00170061,0.00023620,0.00018896,0.00151165,0.00302330,0.00396809,0.00444048,0.00278711,0.00184233,-0.00037791,-0.00165337,-0.00307054,-0.00429876,-0.00467667,-0.00486563,-0.00373189,-0.00278711,-0.00132270,-0.00066135,0.00000000,0.00094478,0.00188957,0.00406257,0.00529078,0.00666072,0.00689691,0.00623557,0.00496011,0.00302330,0.00146441,-0.00028343,-0.00066135,-0.00099202,0.00000000,0.00203128,0.00429876,0.00836133,0.01100672,0.01403002,0.01379383,0.01218770,0.00774722,0.00259815,-0.00203128,-0.00529078,-0.00642452,-0.00599937,-0.00486563,-0.00368465,-0.00307054,-0.00259815,-0.00325950,-0.00425152,-0.00529078,-0.00746378,-0.00694415,-0.00708587,-0.00410980,-0.00165337,0.00160613,0.00425152,0.00614109,0.00793617,0.00935335,0.00949507,0.00897544,0.00703863,0.00453496,0.00207852,-0.00018896,-0.00321226,-0.00491287,-0.00798341,-0.00873924,-0.00883372,-0.00562146,-0.00037791,0.00590489,0.01284904,0.01558891,0.01606131,0.01091224,0.00373189,-0.00283435,-0.00604661,-0.00462944,0.00047239,0.00585765,0.00982574,0.01077052,0.00940059,0.00708587,0.00401533,0.00184233,-0.00099202,-0.00136993,-0.00188957,0.00023620,0.00151165,0.00273987,0.00240920,0.00127546,0.00037791,0.00000000,0.00037791,0.00000000,-0.00099202,-0.00401533,-0.00718035,-0.01110120,-0.01355763,-0.01421898,-0.01266009,-0.00831409,-0.00505459,-0.00132270,-0.00226748,-0.00415704,-0.00736931,-0.00944783,-0.00892820,-0.00675520,-0.00491287,-0.00316502,-0.00335398,-0.00363741,-0.00335398,-0.00264539,-0.00089754,0.00014172,0.00094478,0.00047239,-0.00042515,-0.00188957,-0.00307054,-0.00392085,-0.00439324,-0.00406257,-0.00415704,-0.00344846,-0.00297607,-0.00269263,-0.00226748,-0.00269263,-0.00240920,-0.00236196,-0.00075583,0.00103926,0.00335398,0.00434600,0.00434600,0.00335398,0.00245644,0.00288159,0.00302330,0.00481839,0.00477115,0.00496011,0.00392085,0.00217300,0.00047239,-0.00203128,-0.00415704,-0.00703863,-0.00821961,-0.01001470,-0.01001470,-0.00940059,-0.00821961,-0.00590489,-0.00429876,-0.00344846,-0.00273987,-0.00420428,-0.00396809,-0.00481839,-0.00316502,-0.00188957,0.00000000,0.00028343,0.00000000,-0.00113374,-0.00207852,-0.00292883,-0.00283435,-0.00316502,-0.00330674,-0.00439324,-0.00538526,-0.00666072,-0.00647176,-0.00595213,-0.00415704,-0.00278711,-0.00179509,-0.00146441,-0.00174785,-0.00179509,-0.00160613,-0.00118098,-0.00061411,-0.00113374,-0.00127546,-0.00255091,-0.00217300,-0.00217300,0.00014172,0.00207852,0.00472391,0.00604661,0.00651900,0.00623557,0.00524354,0.00448772,0.00401533,0.00321226,0.00316502,0.00179509,0.00066135,-0.00127546,-0.00316502,-0.00500735,-0.00491287,-0.00453496,-0.00103926,0.00170061,0.00472391,0.00571594,0.00496011,0.00292883,0.00033067,-0.00155889,-0.00255091,-0.00307054,-0.00250367,-0.00245644,-0.00207852,-0.00160613,-0.00198404,-0.00099202,-0.00151165,-0.00023620,-0.00118098,-0.00085030,-0.00184233,-0.00226748,-0.00245644,-0.00217300,-0.00222024,-0.00122822,-0.00165337,-0.00061411,-0.00075583,0.00066135,0.00160613,0.00335398,0.00538526,0.00736931,0.00930611,0.00973126,0.00996746,0.00751102,0.00614109,0.00344846,0.00273987,0.00198404,0.00316502,0.00344846,0.00486563,0.00524354,0.00599937,0.00666072,0.00713311,0.00751102,0.00760550,0.00675520,0.00614109,0.00486563,0.00453496,0.00486563,0.00618833,0.00807789,0.00925887,0.00958954,0.00845581,0.00647176,0.00387361,0.00099202,-0.00099202,-0.00269263,-0.00273987,-0.00316502,-0.00207852,-0.00198404,-0.00037791,0.00047239,0.00250367,0.00415704,0.00538526,0.00661348,0.00566870,0.00500735,0.00269263,-0.00028343,-0.00264539,-0.00533802,-0.00623557,-0.00661348,-0.00533802,-0.00491287,-0.00392085,-0.00410980,-0.00401533,-0.00382637,-0.00283435,-0.00188957,-0.00103926,0.00023620,0.00037791,0.00269263,0.00330674,0.00543250,0.00543250,0.00562146,0.00448772,0.00330674,0.00160613,0.00108650,0.00051963,0.00165337,0.00297607,0.00458220,0.00604661,0.00618833,0.00614109,0.00491287,0.00481839,0.00387361,0.00477115,0.00415704,0.00477115,0.00425152,0.00444048,0.00387361,0.00467667,0.00477115,0.00609385,0.00661348,0.00642452,0.00514907,0.00283435,-0.00009448,-0.00264539,-0.00406257,-0.00481839,-0.00392085,-0.00311778,-0.00179509,-0.00051963,0.00009448,0.00132270,0.00151165,0.00222024,0.00273987,0.00231472,0.00278711,0.00099202,0.00000000,-0.00250367,-0.00425152,-0.00538526,-0.00599937,-0.00481839,-0.00382637,-0.00155889,-0.00089754,0.00004724,-0.00009448,-0.00061411,0.00000000,-0.00075583,0.00037791,0.00014172,0.00085030,0.00103926,0.00184233,0.00198404,0.00325950,0.00288159,0.00340122,0.00236196,0.00283435,0.00255091,0.00382637,0.00462944,0.00566870,0.00637728,0.00566870,0.00505459,0.00344846,0.00349570,0.00344846,0.00491287,0.00609385,0.00684967,0.00703863,0.00628280,0.00510183,0.00401533,0.00297607,0.00236196,0.00193680,0.00236196,0.00325950,0.00533802,0.00736931,0.00916439,0.01006194,0.01015641,0.00911715,0.00784170,0.00566870,0.00429876,0.00226748,0.00198404,0.00080307,0.00136993,0.00165337,0.00302330,0.00415704,0.00529078,0.00562146,0.00552698,0.00434600,0.00273987,0.00103926,-0.00061411,-0.00127546,-0.00226748,-0.00255091,-0.00344846,-0.00392085,-0.00491287,-0.00462944,-0.00491287,-0.00382637,-0.00330674,-0.00231472,-0.00222024,-0.00174785,-0.00207852,-0.00122822,-0.00070859,0.00085030,0.00226748,0.00288159,0.00420428,0.00373189,0.00448772,0.00410980,0.00425152,0.00392085,0.00354294,0.00307054,0.00297607,0.00231472,0.00283435,0.00245644,0.00311778,0.00382637,0.00439324,0.00566870,0.00604661,0.00713311,0.00817237,0.00911715,0.00987298,0.00968402,0.00774722,0.00524354,0.00188957,-0.00070859,-0.00188957,-0.00198404,-0.00122822,-0.00037791,0.00061411,0.00080307,0.00170061,0.00141717,0.00174785,0.00122822,0.00070859,0.00004724,-0.00080307,-0.00160613,-0.00283435,-0.00387361,-0.00458220,-0.00552698,-0.00500735,-0.00505459,-0.00425152,-0.00325950,-0.00255091,-0.00094478,0.00018896,0.00118098,0.00207852,0.00118098,0.00174785,0.00037791,0.00085030,0.00089754,0.00151165,0.00207852,0.00240920,0.00231472,0.00255091,0.00240920,0.00231472,0.00212576,0.00198404,0.00165337,0.00188957,0.00132270,0.00103926,-0.00061411,-0.00198404,-0.00425152,-0.00510183,-0.00562146,-0.00458220,-0.00321226,-0.00051963,0.00103926,0.00401533,0.00505459,0.00656624,0.00703863,0.00703863,0.00708587,0.00656624,0.00666072,0.00618833,0.00623557,0.00581041,0.00477115,0.00387361,0.00212576,0.00028343,-0.00160613,-0.00434600,-0.00633004,-0.00859752,-0.00963678,-0.01020365,-0.00897544,-0.00765274,-0.00496011,-0.00302330,-0.00042515,0.00099202,0.00307054,0.00354294,0.00448772,0.00363741,0.00250367,0.00094478,-0.00127546,-0.00193680,-0.00250367,-0.00179509,-0.00042515,0.00018896,0.00118098,0.00113374,0.00113374,0.00085030,0.00080307,0.00089754,0.00094478,0.00080307,0.00118098,0.00118098,0.00207852,0.00259815,0.00387361,0.00429876,0.00566870,0.00581041,0.00661348,0.00618833,0.00585765,0.00510183,0.00448772,0.00448772,0.00500735,0.00604661,0.00732207,0.00779446,0.00812513,0.00765274,0.00736931,0.00684967,0.00680244,0.00670796,0.00614109,0.00547974,0.00368465,0.00188957,0.00056687,-0.00042515,0.00051963,0.00170061,0.00392085,0.00609385,0.00784170,0.00921163,0.00954231,0.00977850,0.00873924,0.00798341,0.00618833,0.00481839,0.00368465,0.00245644,0.00174785,0.00028343,-0.00061411,-0.00231472,-0.00269263,-0.00368465,-0.00203128,-0.00132270,0.00136993,0.00259815,0.00392085,0.00505459,0.00533802,0.00618833,0.00618833,0.00642452,0.00604661,0.00633004,0.00623557,0.00760550,0.00788894,0.00888096,0.00774722,0.00689691,0.00401533,0.00198404,-0.00108650,-0.00245644,-0.00377913,-0.00340122,-0.00288159,-0.00118098,0.00018896,0.00188957,0.00273987,0.00359017,0.00377913,0.00368465,0.00377913,0.00330674,0.00359017,0.00425152,0.00538526,0.00732207,0.00831409,0.00906991,0.00855028,0.00609385,0.00382637,0.00042515,-0.00255091,-0.00420428,-0.00566870,-0.00500735,-0.00377913,-0.00174785,-0.00042515,0.00099202,0.00051963,-0.00004724,-0.00198404,-0.00359017,-0.00529078,-0.00599937,-0.00599937,-0.00406257,-0.00217300,0.00061411,0.00222024,0.00212576,0.00174785,-0.00061411,-0.00217300,-0.00311778,-0.00363741,-0.00217300,-0.00075583,0.00127546,0.00307054,0.00448772,0.00481839,0.00514907,0.00444048,0.00472391,0.00396809,0.00472391,0.00458220,0.00552698,0.00618833,0.00689691,0.00684967,0.00670796,0.00529078,0.00387361,0.00245644,0.00155889,0.00184233,0.00273987,0.00415704,0.00496011,0.00533802,0.00458220,0.00240920,0.00089754,-0.00198404,-0.00264539,-0.00406257,-0.00387361,-0.00448772,-0.00477115,-0.00533802,-0.00552698,-0.00467667,-0.00297607,0.00009448,0.00278711,0.00562146,0.00732207,0.00751102,0.00732207,0.00604661,0.00462944,0.00359017,0.00222024,0.00155889,0.00127546,0.00070859,0.00108650,0.00070859,0.00155889,0.00122822,0.00226748,0.00184233,0.00273987,0.00264539,0.00269263,0.00165337,-0.00037791,-0.00359017,-0.00661348,-0.00902267,-0.00869200,-0.00647176,-0.00155889,0.00311778,0.00680244,0.00798341,0.00595213,0.00292883,-0.00146441,-0.00344846,-0.00505459,-0.00401533,-0.00307054,-0.00160613,-0.00085030,-0.00023620,-0.00061411,0.00018896,-0.00047239,-0.00037791,-0.00127546,-0.00387361,-0.00491287,-0.00878648,-0.00944783,-0.01124291,-0.01143187,-0.01086500,-0.01133739,-0.01152635,-0.01266009,-0.01436070,-0.01473861,-0.01539996,-0.01299076,-0.01110120,-0.00633004,-0.00278711,0.00179509,0.00444048,0.00656624,0.00675520,0.00581041,0.00401533,0.00217300,0.00099202,0.00155889,0.00307054,0.00467667,0.00699139,0.00684967,0.00736931,0.00633004,0.00590489,0.00510183,0.00500735,0.00382637,0.00340122,0.00259815,0.00207852,0.00203128,0.00146441,0.00089754,0.00014172,-0.00023620,-0.00047239,0.00033067,0.00155889,0.00264539,0.00458220,0.00514907,0.00656624,0.00675520,0.00684967,0.00595213,0.00496011,0.00292883,0.00193680,0.00085030,0.00132270,0.00240920,0.00415704,0.00633004,0.00765274,0.00906991,0.00826685,0.00821961,0.00618833,0.00500735,0.00316502,0.00203128,0.00094478,0.00075583,0.00028343,-0.00004724,-0.00075583,-0.00283435,-0.00377913,-0.00637728,-0.00618833,-0.00769998,-0.00684967,-0.00736931,-0.00718035,-0.00727483,-0.00746378,-0.00637728,-0.00566870,-0.00354294,-0.00193680,0.00018896,0.00179509,0.00273987,0.00307054,0.00259815,0.00113374,-0.00004724,-0.00203128,-0.00193680,-0.00118098,0.00179509,0.00500735,0.00897544,0.01162083,0.01388831,0.01403002,0.01426622,0.01166807,0.01015641,0.00623557,0.00288159,0.00004724,-0.00283435,-0.00325950,-0.00392085,-0.00335398,-0.00406257,-0.00434600,-0.00680244,-0.00807789,-0.01034537,-0.01086500,-0.01105396,-0.00977850,-0.00788894,-0.00496011,-0.00226748,0.00080307,0.00311778,0.00510183,0.00604661,0.00703863,0.00703863,0.00779446,0.00760550,0.00798341,0.00765274,0.00666072,0.00609385,0.00344846,0.00273987,0.00047239,0.00037791,-0.00028343,0.00066135,0.00047239,0.00108650,0.00056687,-0.00051963,-0.00132270,-0.00311778,-0.00420428,-0.00547974,-0.00670796,-0.00784170,-0.00897544,-0.01053433,-0.01185702,-0.01284904,-0.01403002,-0.01403002,-0.01398278,-0.01261285,-0.01133739,-0.00925887,-0.00807789,-0.00633004,-0.00477115,-0.00297607,-0.00061411,0.00174785,0.00325950,0.00481839,0.00368465,0.00335398,0.00089754,0.00014172,-0.00066135,-0.00018896,0.00080307,0.00231472,0.00217300,0.00141717,-0.00212576,-0.00637728,-0.01110120,-0.01535272,-0.01752572,-0.01818707,-0.01658094,-0.01417174,-0.01077052,-0.00892820,-0.00628280,-0.00708587,-0.00651900,-0.00845581,-0.00807789,-0.00836133,-0.00618833,-0.00429876,-0.00160613,0.00018896,0.00155889,0.00122822,0.00080307,-0.00047239,-0.00217300,-0.00307054,-0.00401533,-0.00420428,-0.00297607,-0.00207852,-0.00018896,0.00165337,0.00255091,0.00467667,0.00467667,0.00599937,0.00467667,0.00425152,0.00155889,0.00028343,-0.00259815,-0.00316502,-0.00547974,-0.00547974,-0.00718035,-0.00722759,-0.00798341,-0.00826685,-0.00888096,-0.00954231,-0.01077052,-0.01100672,-0.01171531,-0.01006194,-0.00859752,-0.00496011,-0.00174785,0.00203128,0.00462944,0.00637728,0.00651900,0.00543250,0.00368465,0.00155889,0.00000000,-0.00165337,-0.00264539,-0.00349570,-0.00396809,-0.00363741,-0.00349570,-0.00231472,-0.00170061,-0.00118098,-0.00075583,-0.00170061,-0.00193680,-0.00212576,-0.00198404,-0.00037791,0.00075583,0.00222024,0.00236196,0.00212576,0.00037791,-0.00099202,-0.00307054,-0.00496011,-0.00623557,-0.00736931,-0.00736931,-0.00708587,-0.00684967,-0.00628280,-0.00680244,-0.00732207,-0.00826685,-0.00883372,-0.00921163,-0.00878648,-0.00788894,-0.00651900,-0.00425152,-0.00236196,-0.00023620,0.00047239,0.00155889,0.00085030,0.00141717,0.00070859,0.00108650,0.00066135,0.00070859,-0.00018896,-0.00018896,-0.00094478,-0.00066135,-0.00037791,0.00075583,0.00151165,0.00288159,0.00269263,0.00302330,0.00136993,0.00023620,-0.00217300,-0.00410980,-0.00571594,-0.00703863,-0.00633004,-0.00467667,-0.00198404,0.00165337,0.00363741,0.00510183,0.00415704,0.00222024,-0.00033067,-0.00222024,-0.00354294,-0.00302330,-0.00283435,-0.00207852,-0.00155889,-0.00273987,-0.00245644,-0.00406257,-0.00354294,-0.00354294,-0.00302330,-0.00193680,-0.00122822,-0.00023620,0.00094478,0.00141717,0.00217300,0.00198404,0.00141717,0.00004724,-0.00127546,-0.00222024,-0.00330674,-0.00240920,-0.00207852,-0.00061411,0.00108650,0.00207852,0.00368465,0.00486563,0.00614109,0.00807789,0.00883372,0.01058157,0.00992022,0.00987298,0.00817237,0.00708587,0.00557422,0.00514907,0.00406257,0.00349570,0.00174785,-0.00018896,-0.00217300,-0.00415704,-0.00510183,-0.00552698,-0.00552698,-0.00481839,-0.00505459,-0.00425152,-0.00434600,-0.00410980,-0.00377913,-0.00373189,-0.00255091,-0.00174785,0.00023620,0.00099202,0.00250367,0.00236196,0.00250367,0.00245644,0.00155889,0.00141717,-0.00080307,-0.00222024,-0.00585765,-0.00774722,-0.01029813,-0.01058157,-0.00944783,-0.00788894,-0.00448772,-0.00245644,-0.00066135,-0.00004724,-0.00037791,-0.00066135,-0.00056687,-0.00028343,0.00075583,0.00127546,0.00226748,0.00264539,0.00325950,0.00392085,0.00453496,0.00510183,0.00458220,0.00359017,0.00193680,0.00000000,-0.00099202,-0.00264539,-0.00264539,-0.00340122,-0.00392085,-0.00477115,-0.00675520,-0.00812513,-0.00987298,-0.01034537,-0.01053433,-0.00963678,-0.00892820,-0.00864476,-0.00812513,-0.00902267,-0.00888096,-0.00940059,-0.00902267,-0.00788894,-0.00694415,-0.00500735,-0.00321226,-0.00127546,0.00108650,0.00240920,0.00410980,0.00420428,0.00439324,0.00307054,0.00236196,0.00160613,0.00136993,0.00240920,0.00226748,0.00363741,0.00283435,0.00325950,0.00278711,0.00359017,0.00481839,0.00623557,0.00708587,0.00736931,0.00623557,0.00434600,0.00264539,0.00018896,-0.00009448,-0.00108650,-0.00018896,0.00103926,0.00231472,0.00486563,0.00581041,0.00694415,0.00718035,0.00581041,0.00448772,0.00198404,-0.00042515,-0.00330674,-0.00543250,-0.00760550,-0.00840857,-0.00892820,-0.00803065,-0.00708587,-0.00524354,-0.00434600,-0.00316502,-0.00292883,-0.00292883,-0.00382637,-0.00505459,-0.00666072,-0.00803065,-0.00892820,-0.00949507,-0.00902267,-0.00855028,-0.00779446,-0.00732207,-0.00694415,-0.00684967,-0.00590489,-0.00571594,-0.00444048,-0.00359017,-0.00231472,-0.00122822,-0.00085030,-0.00103926,-0.00188957,-0.00297607,-0.00505459,-0.00604661,-0.00817237,-0.00883372,-0.00958954,-0.00958954,-0.00826685,-0.00722759,-0.00481839,-0.00330674,-0.00165337,-0.00051963,0.00033067,0.00146441,0.00226748,0.00344846,0.00330674,0.00325950,0.00193680,0.00113374,0.00009448,0.00118098,0.00179509,0.00392085,0.00434600,0.00373189,0.00198404,-0.00094478,-0.00302330,-0.00448772,-0.00467667,-0.00368465,-0.00307054,-0.00136993,-0.00108650,-0.00028343,-0.00004724,-0.00009448,0.00000000,0.00018896,0.00056687,0.00198404,0.00283435,0.00453496,0.00496011,0.00524354,0.00510183,0.00316502,0.00203128,-0.00061411,-0.00198404,-0.00396809,-0.00425152,-0.00467667,-0.00396809,-0.00269263,-0.00245644,-0.00085030,-0.00113374,0.00000000,0.00037791,0.00165337,0.00283435,0.00377913,0.00439324,0.00425152,0.00354294,0.00335398,0.00273987,0.00382637,0.00448772,0.00642452,0.00755826,0.00878648,0.00916439,0.00916439,0.00845581,0.00755826,0.00642452,0.00481839,0.00325950,0.00103926,-0.00061411,-0.00278711,-0.00401533,-0.00519630,-0.00599937,-0.00656624,-0.00718035,-0.00779446,-0.00788894,-0.00807789,-0.00817237,-0.00718035,-0.00666072,-0.00481839,-0.00302330,-0.00089754,0.00136993,0.00250367,0.00387361,0.00354294,0.00321226,0.00184233,0.00051963,-0.00089754,-0.00198404,-0.00264539,-0.00250367,-0.00193680,-0.00108650,0.00042515,0.00118098,0.00278711,0.00311778,0.00420428,0.00368465,0.00429876,0.00359017,0.00434600,0.00406257,0.00467667,0.00363741,0.00292883,0.00155889,0.00009448,-0.00037791,-0.00118098,0.00000000,0.00018896,0.00231472,0.00222024,0.00307054,0.00170061,0.00094478,-0.00108650,-0.00113374,-0.00170061,-0.00099202,-0.00028343,0.00033067,0.00080307,0.00136993,0.00061411,0.00014172,-0.00155889,-0.00278711,-0.00377913,-0.00359017,-0.00311778,-0.00179509,-0.00033067,0.00061411,0.00273987,0.00321226,0.00510183,0.00519630,0.00618833,0.00609385,0.00609385,0.00562146,0.00533802,0.00444048,0.00387361,0.00349570,0.00255091,0.00283435,0.00198404,0.00146441,0.00061411,0.00009448,0.00042515,0.00122822,0.00259815,0.00373189,0.00453496,0.00429876,0.00453496,0.00311778,0.00325950,0.00136993,0.00051963,-0.00099202,-0.00217300,-0.00245644,-0.00264539,-0.00160613,-0.00141717,-0.00080307,-0.00184233,-0.00207852,-0.00283435,-0.00297607,-0.00269263,-0.00344846,-0.00410980,-0.00661348,-0.00812513,-0.01067604,-0.01010917,-0.00940059,-0.00595213,-0.00231472,0.00146441,0.00462944,0.00604661,0.00689691,0.00647176,0.00633004,0.00581041,0.00628280,0.00585765,0.00590489,0.00486563,0.00363741,0.00264539,0.00188957,0.00231472,0.00325950,0.00434600,0.00529078,0.00566870,0.00533802,0.00477115,0.00382637,0.00330674,0.00273987,0.00321226,0.00278711,0.00363741,0.00297607,0.00321226,0.00222024,0.00165337,0.00014172,-0.00080307,-0.00255091,-0.00292883,-0.00321226,-0.00226748,-0.00132270,-0.00023620,-0.00047239,-0.00033067,-0.00146441,-0.00174785,-0.00174785,-0.00160613,-0.00061411,-0.00023620,0.00028343,0.00033067,0.00009448,0.00051963,0.00009448,0.00146441,0.00240920,0.00434600,0.00609385,0.00741654,0.00769998,0.00722759,0.00628280,0.00425152,0.00311778,0.00136993,0.00033067,0.00085030,0.00080307,0.00377913,0.00462944,0.00689691,0.00684967,0.00651900,0.00524354,0.00439324,0.00363741,0.00458220,0.00453496,0.00651900,0.00661348,0.00765274,0.00774722,0.00736931,0.00642452,0.00576317,0.00354294,0.00321226,0.00146441,0.00151165,0.00127546,0.00188957,0.00283435,0.00288159,0.00316502,0.00193680,0.00061411,-0.00118098,-0.00330674,-0.00368465,-0.00477115,-0.00273987,-0.00222024,0.00033067,0.00184233,0.00302330,0.00377913,0.00269263,0.00217300,-0.00014172,-0.00127546,-0.00288159,-0.00255091,-0.00278711,-0.00085030,-0.00070859,0.00155889,0.00203128,0.00321226,0.00410980,0.00340122,0.00340122,0.00056687,-0.00085030,-0.00340122,-0.00491287,-0.00576317,-0.00661348,-0.00637728,-0.00666072,-0.00590489,-0.00538526,-0.00354294,-0.00250367,-0.00023620,0.00023620,0.00236196,0.00269263,0.00467667,0.00599937,0.00751102,0.00930611,0.00906991,0.00864476,0.00628280,0.00335398,-0.00028343,-0.00325950,-0.00576317,-0.00642452,-0.00656624,-0.00595213,-0.00566870,-0.00529078,-0.00571594,-0.00585765,-0.00590489,-0.00571594,-0.00477115,-0.00429876,-0.00349570,-0.00283435,-0.00273987,-0.00165337,-0.00217300,-0.00155889,-0.00316502,-0.00382637,-0.00651900,-0.00793617,-0.01029813,-0.01114844,-0.01185702,-0.01185702,-0.01162083,-0.01199874,-0.01162083,-0.01251837,-0.01251837,-0.01388831,-0.01417174,-0.01506928,-0.01440794,-0.01374659,-0.01162083,-0.00968402,-0.00741654,-0.00533802,-0.00406257,-0.00292883,-0.00259815,-0.00302330,-0.00330674,-0.00491287,-0.00510183,-0.00618833,-0.00557422,-0.00519630,-0.00354294,-0.00231472,-0.00014172,0.00103926,0.00311778,0.00401533,0.00514907,0.00505459,0.00448772,0.00273987,0.00108650,-0.00127546,-0.00330674,-0.00448772,-0.00543250,-0.00557422,-0.00500735,-0.00481839,-0.00354294,-0.00292883,-0.00193680,-0.00132270,-0.00075583,-0.00108650,-0.00061411,-0.00240920,-0.00264539,-0.00477115,-0.00543250,-0.00661348,-0.00604661,-0.00552698,-0.00373189,-0.00250367,-0.00061411,0.00004724,0.00132270,0.00122822,0.00146441,0.00136993,0.00113374,0.00141717,0.00151165,0.00179509,0.00240920,0.00240920,0.00255091,0.00302330,0.00307054,0.00425152,0.00429876,0.00538526,0.00514907,0.00543250,0.00486563,0.00425152,0.00316502,0.00217300,0.00075583,-0.00051963,-0.00174785,-0.00283435,-0.00382637,-0.00382637,-0.00401533,-0.00330674,-0.00207852,-0.00122822,0.00037791,0.00042515,0.00085030,-0.00070859,-0.00122822,-0.00321226,-0.00316502,-0.00373189,-0.00292883,-0.00184233,-0.00070859,0.00113374,0.00288159,0.00425152,0.00557422,0.00562146,0.00529078,0.00415704,0.00340122,0.00203128,0.00240920,0.00193680,0.00269263,0.00307054,0.00307054,0.00273987,0.00160613,-0.00061411,-0.00273987,-0.00566870,-0.00788894,-0.00944783,-0.00977850,-0.00940059,-0.00803065,-0.00713311,-0.00571594,-0.00543250,-0.00448772,-0.00462944,-0.00401533,-0.00401533,-0.00410980,-0.00462944,-0.00557422,-0.00576317,-0.00576317,-0.00444048,-0.00307054,-0.00132270,-0.00047239,-0.00018896,-0.00103926,-0.00240920,-0.00335398,-0.00429876,-0.00392085,-0.00307054,-0.00212576,-0.00141717,-0.00103926,-0.00222024,-0.00259815,-0.00439324,-0.00444048,-0.00529078,-0.00439324,-0.00321226,-0.00146441,0.00151165,0.00349570,0.00599937,0.00765274,0.00798341,0.00845581,0.00670796,0.00562146,0.00387361,0.00259815,0.00283435,0.00278711,0.00401533,0.00425152,0.00458220,0.00429876,0.00462944,0.00472391,0.00519630,0.00514907,0.00415704,0.00349570,0.00250367,0.00240920,0.00325950,0.00349570,0.00472391,0.00458220,0.00477115,0.00307054,0.00250367,-0.00042515,-0.00113374,-0.00340122,-0.00316502,-0.00330674,-0.00184233,-0.00127546,-0.00099202,-0.00108650,-0.00222024,-0.00250367,-0.00392085,-0.00415704,-0.00529078,-0.00552698,-0.00604661,-0.00585765,-0.00533802,-0.00401533,-0.00269263,-0.00014172,0.00146441,0.00401533,0.00538526,0.00689691,0.00831409,0.00949507,0.01095948,0.01119567,0.01119567,0.00968402,0.00727483,0.00496011,0.00127546,-0.00051963,-0.00288159,-0.00278711,-0.00273987,-0.00066135,0.00103926,0.00354294,0.00477115,0.00609385,0.00614109,0.00614109,0.00543250,0.00486563,0.00434600,0.00472391,0.00505459,0.00642452,0.00746378,0.00836133,0.00821961,0.00765274,0.00581041,0.00410980,0.00245644,0.00108650,0.00056687,0.00009448,-0.00004724,-0.00033067,-0.00061411,-0.00103926,-0.00118098,-0.00136993,-0.00184233,-0.00222024,-0.00368465,-0.00453496,-0.00595213,-0.00670796,-0.00736931,-0.00718035,-0.00784170,-0.00760550,-0.00840857,-0.00888096,-0.00812513,-0.00760550,-0.00505459,-0.00240920,0.00023620,0.00283435,0.00354294,0.00415704,0.00269263,0.00212576,-0.00023620,-0.00080307,-0.00198404,-0.00222024,-0.00165337,-0.00132270,-0.00061411,0.00103926,0.00108650,0.00354294,0.00344846,0.00552698,0.00519630,0.00647176,0.00590489,0.00566870,0.00439324,0.00278711,0.00127546,0.00028343,-0.00033067,0.00037791,0.00023620,0.00103926,0.00075583,0.00047239,0.00080307,0.00061411,0.00174785,0.00288159,0.00434600,0.00566870,0.00618833,0.00628280,0.00491287,0.00377913,0.00122822,0.00023620,-0.00099202,-0.00070859,0.00047239,0.00222024,0.00552698,0.00793617,0.01119567,0.01209322,0.01266009,0.01095948,0.00944783,0.00656624,0.00467667,0.00207852,0.00056687,-0.00103926,-0.00165337,-0.00184233,-0.00184233,-0.00170061,-0.00250367,-0.00292883,-0.00434600,-0.00458220,-0.00481839,-0.00481839,-0.00420428,-0.00444048,-0.00420428,-0.00486563,-0.00496011,-0.00590489,-0.00562146,-0.00566870,-0.00500735,-0.00368465,-0.00273987,-0.00122822,-0.00018896,0.00155889,0.00236196,0.00373189,0.00354294,0.00344846,0.00207852,0.00070859,-0.00075583,-0.00198404,-0.00288159,-0.00325950,-0.00387361,-0.00307054,-0.00335398,-0.00222024,-0.00188957,-0.00070859,0.00066135,0.00179509,0.00255091,0.00307054,0.00283435,0.00207852,0.00165337,0.00061411,0.00066135,0.00047239,0.00103926,0.00113374,0.00198404,0.00179509,0.00231472,0.00203128,0.00207852,0.00193680,0.00222024,0.00259815,0.00307054,0.00382637,0.00377913,0.00477115,0.00382637,0.00377913,0.00179509,0.00028343,-0.00170061,-0.00340122,-0.00467667,-0.00538526,-0.00614109,-0.00633004,-0.00675520,-0.00661348,-0.00604661,-0.00524354,-0.00429876,-0.00307054,-0.00245644,-0.00141717,-0.00042515,0.00028343,0.00155889,0.00203128,0.00307054,0.00311778,0.00368465,0.00344846,0.00330674,0.00373189,0.00349570,0.00425152,0.00472391,0.00500735,0.00609385,0.00623557,0.00666072,0.00628280,0.00547974,0.00396809,0.00363741,0.00273987,0.00434600,0.00538526,0.00765274,0.00840857,0.00944783,0.00878648,0.00888096,0.00817237,0.00831409,0.00803065,0.00793617,0.00736931,0.00699139,0.00519630,0.00448772,0.00222024,0.00174785,0.00080307,0.00222024,0.00330674,0.00524354,0.00718035,0.00755826,0.00793617,0.00703863,0.00519630,0.00335398,0.00122822,-0.00094478,-0.00245644,-0.00354294,-0.00505459,-0.00562146,-0.00755826,-0.00859752,-0.00982574,-0.01015641,-0.00930611,-0.00779446,-0.00533802,-0.00250367,-0.00061411,0.00141717,0.00203128,0.00236196,0.00231472,0.00160613,0.00136993,0.00094478,0.00099202,0.00132270,0.00184233,0.00226748,0.00193680,0.00094478,-0.00132270,-0.00278711,-0.00321226,-0.00212576,0.00160613,0.00486563,0.00892820,0.01081776,0.01185702,0.01143187,0.01048709,0.00906991,0.00746378,0.00633004,0.00491287,0.00486563,0.00453496,0.00467667,0.00500735,0.00472391,0.00519630,0.00547974,0.00614109,0.00670796,0.00599937,0.00557422,0.00354294,0.00259815,0.00132270,0.00080307,0.00080307,0.00056687,0.00033067,-0.00004724,-0.00004724,0.00014172,0.00103926,0.00118098,0.00103926,-0.00113374,-0.00477115,-0.00869200,-0.01190426,-0.01190426,-0.00930611,-0.00425152,0.00075583,0.00415704,0.00543250,0.00462944,0.00415704,0.00396809,0.00410980,0.00429876,0.00278711,0.00000000,-0.00340122,-0.00637728,-0.00817237,-0.00788894,-0.00633004,-0.00453496,-0.00250367,-0.00264539,-0.00297607,-0.00505459,-0.00661348,-0.00661348,-0.00628280,-0.00255091,-0.00127546,0.00080307,-0.00014172,-0.00217300,-0.00340122,-0.00448772,-0.00344846,-0.00198404,-0.00089754,0.00004724,-0.00132270,-0.00160613,-0.00396809,-0.00396809,-0.00529078,-0.00529078,-0.00571594,-0.00566870,-0.00505459,-0.00467667,-0.00330674,-0.00236196,-0.00047239,0.00108650,0.00335398,0.00538526,0.00718035,0.00906991,0.00963678,0.01015641,0.00996746,0.00897544,0.00855028,0.00699139,0.00618833,0.00519630,0.00415704,0.00392085,0.00302330,0.00311778,0.00302330,0.00292883,0.00245644,0.00198404,0.00146441,0.00066135,0.00108650,-0.00033067,-0.00018896,-0.00207852,-0.00325950,-0.00533802,-0.00618833,-0.00784170,-0.00784170,-0.00826685,-0.00859752,-0.00836133,-0.00888096,-0.00883372,-0.00850304,-0.00821961,-0.00741654,-0.00684967,-0.00684967,-0.00699139,-0.00788894,-0.00855028,-0.00973126,-0.00954231,-0.01053433,-0.00963678,-0.00897544,-0.00746378,-0.00453496,-0.00179509,0.00051963,0.00264539,0.00292883,0.00368465,0.00425152,0.00406257,0.00311778,-0.00094478,-0.00637728,-0.01251837,-0.01521100,-0.01379383,-0.00595213,0.00415704,0.01454965,0.02116313,0.02215515,0.01847050,0.01129015,0.00425152,-0.00207852,-0.00543250,-0.00647176,-0.00595213,-0.00297607,-0.00075583,0.00264539,0.00448772,0.00557422,0.00477115,0.00302330,0.00009448,-0.00212576,-0.00382637,-0.00396809,-0.00392085,-0.00288159,-0.00307054,-0.00217300,-0.00170061,-0.00023620,0.00165337,0.00316502,0.00467667,0.00566870,0.00661348,0.00807789,0.00878648,0.00878648,0.00736931,0.00425152,0.00174785,-0.00151165,-0.00273987,-0.00292883,-0.00198404,0.00061411,0.00240920,0.00510183,0.00637728,0.00741654,0.00718035,0.00746378,0.00713311,0.00892820,0.00973126,0.01105396,0.01110120,0.01025089,0.00906991,0.00817237,0.00675520,0.00637728,0.00500735,0.00335398,0.00203128,-0.00056687,-0.00179509,-0.00396809,-0.00510183,-0.00642452,-0.00732207,-0.00807789,-0.00906991,-0.00944783,-0.01124291,-0.01171531,-0.01369935,-0.01360487,-0.01341591,-0.01204598,-0.00992022,-0.00812513,-0.00609385,-0.00481839,-0.00297607,-0.00193680,-0.00009448,0.00122822,0.00269263,0.00311778,0.00415704,0.00444048,0.00533802,0.00538526,0.00486563,0.00307054,0.00127546,-0.00127546,-0.00250367,-0.00335398,-0.00302330,-0.00179509,-0.00094478,0.00047239,0.00151165,0.00250367,0.00382637,0.00415704,0.00439324,0.00302330,0.00146441,-0.00028343,-0.00179509,-0.00127546,-0.00108650,0.00080307,0.00165337,0.00245644,0.00255091,0.00250367,0.00207852,0.00236196,0.00151165,0.00184233,0.00085030,0.00141717,0.00179509,0.00368465,0.00543250,0.00784170,0.00958954,0.01053433,0.01124291,0.01058157,0.01100672,0.01105396,0.01138463,0.01294352,0.01289628,0.01440794,0.01369935,0.01355763,0.01204598,0.01006194,0.00803065,0.00604661,0.00524354,0.00571594,0.00722759,0.00949507,0.01152635,0.01266009,0.01317972,0.01204598,0.01105396,0.00817237,0.00566870,0.00179509,-0.00113374,-0.00321226,-0.00373189,-0.00259815,-0.00075583,0.00174785,0.00302330,0.00486563,0.00500735,0.00599937,0.00609385,0.00604661,0.00529078,0.00392085,0.00203128,0.00033067,-0.00155889,-0.00217300,-0.00316502,-0.00307054,-0.00377913,-0.00387361,-0.00458220,-0.00448772,-0.00458220,-0.00377913,-0.00359017,-0.00292883,-0.00269263,-0.00240920,-0.00155889,-0.00075583,0.00023620,0.00203128,0.00240920,0.00335398,0.00264539,0.00207852,0.00047239,-0.00014172,-0.00113374,-0.00075583,-0.00061411,-0.00033067,-0.00099202,-0.00184233,-0.00368465,-0.00462944,-0.00628280,-0.00628280,-0.00694415,-0.00694415,-0.00670796,-0.00699139,-0.00623557,-0.00628280,-0.00533802,-0.00467667,-0.00316502,-0.00212576,-0.00146441,-0.00113374,-0.00226748,-0.00325950,-0.00486563,-0.00628280,-0.00670796,-0.00680244,-0.00651900,-0.00538526,-0.00538526,-0.00481839,-0.00505459,-0.00491287,-0.00444048,-0.00349570,-0.00203128,-0.00023620,0.00108650,0.00203128,0.00203128,0.00141717,0.00018896,-0.00108650,-0.00245644,-0.00264539,-0.00273987,-0.00184233,-0.00165337,-0.00188957,-0.00212576,-0.00321226,-0.00359017,-0.00377913,-0.00387361,-0.00307054,-0.00250367,-0.00188957,-0.00061411,-0.00014172,0.00141717,0.00155889,0.00226748,0.00222024,0.00231472,0.00259815,0.00278711,0.00297607,0.00335398,0.00288159,0.00325950,0.00292883,0.00316502,0.00373189,0.00373189,0.00448772,0.00448772,0.00467667,0.00477115,0.00453496,0.00486563,0.00538526,0.00618833,0.00765274,0.00958954,0.01124291,0.01327420,0.01398278,0.01464413,0.01412450,0.01299076,0.01147911,0.00963678,0.00831409,0.00746378,0.00699139,0.00703863,0.00666072,0.00614109,0.00566870,0.00448772,0.00415704,0.00363741,0.00349570,0.00410980,0.00477115,0.00585765,0.00684967,0.00821961,0.00921163,0.00977850,0.01006194,0.00963678,0.00892820,0.00821961,0.00727483,0.00642452,0.00623557,0.00637728,0.00647176,0.00722759,0.00666072,0.00647176,0.00496011,0.00349570,0.00160613,0.00061411,0.00061411,0.00160613,0.00420428,0.00642452,0.00883372,0.00949507,0.00883372,0.00736931,0.00529078,0.00325950,0.00184233,-0.00051963,-0.00165337,-0.00373189,-0.00415704,-0.00429876,-0.00311778,-0.00179509,-0.00028343,0.00075583,0.00056687,0.00066135,-0.00094478,-0.00165337,-0.00240920,-0.00165337,-0.00018896,0.00226748,0.00481839,0.00684967,0.00864476,0.00916439,0.00935335,0.00888096,0.00831409,0.00718035,0.00623557,0.00481839,0.00354294,0.00203128,0.00127546,0.00037791,0.00075583,0.00113374,0.00179509,0.00330674,0.00392085,0.00571594,0.00670796,0.00807789,0.00925887,0.00977850,0.00996746,0.00930611,0.00831409,0.00661348,0.00510183,0.00278711,0.00136993,-0.00094478,-0.00118098,-0.00236196,-0.00188957,-0.00212576,-0.00113374,-0.00141717,-0.00033067,-0.00051963,0.00014172,0.00047239,0.00094478,0.00070859,0.00113374,0.00061411,0.00061411,0.00056687,0.00075583,0.00146441,0.00146441,0.00226748,0.00207852,0.00283435,0.00330674,0.00415704,0.00562146,0.00595213,0.00741654,0.00666072,0.00713311,0.00599937,0.00599937,0.00576317,0.00590489,0.00666072,0.00699139,0.00741654,0.00760550,0.00718035,0.00637728,0.00562146,0.00401533,0.00311778,0.00160613,0.00089754,-0.00023620,-0.00051963,-0.00184233,-0.00212576,-0.00245644,-0.00240920,-0.00094478,0.00042515,0.00203128,0.00354294,0.00439324,0.00453496,0.00538526,0.00472391,0.00500735,0.00373189,0.00222024,0.00000000,-0.00174785,-0.00377913,-0.00321226,-0.00316502,-0.00075583,0.00151165,0.00340122,0.00519630,0.00566870,0.00524354,0.00496011,0.00359017,0.00307054,0.00184233,0.00033067,-0.00170061,-0.00415704,-0.00642452,-0.00859752,-0.01006194,-0.01058157,-0.01010917,-0.00831409,-0.00633004,-0.00283435,-0.00080307,0.00264539,0.00401533,0.00590489,0.00637728,0.00647176,0.00519630,0.00368465,0.00174785,0.00000000,-0.00080307,-0.00075583,0.00000000,0.00132270,0.00226748,0.00316502,0.00340122,0.00269263,0.00165337,-0.00080307,-0.00240920,-0.00538526,-0.00633004,-0.00784170,-0.00736931,-0.00661348,-0.00519630,-0.00439324,-0.00278711,-0.00278711,-0.00184233,-0.00184233,-0.00127546,-0.00151165,-0.00174785,-0.00273987,-0.00444048,-0.00581041,-0.00779446,-0.00840857,-0.00845581,-0.00675520,-0.00448772,-0.00141717,0.00099202,0.00288159,0.00368465,0.00354294,0.00259815,0.00132270,-0.00047239,-0.00151165,-0.00297607,-0.00292883,-0.00269263,-0.00155889,0.00004724,0.00146441,0.00269263,0.00359017,0.00340122,0.00288159,0.00165337,-0.00051963,-0.00240920,-0.00444048,-0.00604661,-0.00633004,-0.00524354,-0.00349570,-0.00023620,0.00259815,0.00448772,0.00599937,0.00590489,0.00566870,0.00519630,0.00448772,0.00349570,0.00236196,0.00023620,-0.00212576,-0.00486563,-0.00722759,-0.00873924,-0.00921163,-0.00840857,-0.00651900,-0.00458220,-0.00212576,-0.00160613,-0.00066135,-0.00132270,-0.00160613,-0.00174785,-0.00198404,-0.00127546,-0.00103926,-0.00042515,-0.00080307,-0.00099202,-0.00203128,-0.00288159,-0.00448772,-0.00557422,-0.00718035,-0.00793617,-0.00944783,-0.00963678,-0.01105396,-0.01058157,-0.01105396,-0.01006194,-0.00954231,-0.00864476,-0.00831409,-0.00836133,-0.00921163,-0.01025089,-0.01209322,-0.01303800,-0.01388831,-0.01384107,-0.01280181,-0.01129015,-0.00935335,-0.00675520,-0.00472391,-0.00212576,-0.00070859,0.00070859,0.00042515,0.00042515,-0.00080307,-0.00113374,-0.00198404,-0.00222024,-0.00273987,-0.00288159,-0.00330674,-0.00311778,-0.00325950,-0.00316502,-0.00335398,-0.00420428,-0.00477115,-0.00557422,-0.00595213,-0.00628280,-0.00661348,-0.00708587,-0.00760550,-0.00793617,-0.00760550,-0.00656624,-0.00519630,-0.00349570,-0.00335398,-0.00330674,-0.00524354,-0.00760550,-0.01043985,-0.01303800,-0.01473861,-0.01535272,-0.01535272,-0.01426622,-0.01317972,-0.01152635,-0.01053433,-0.00850304,-0.00769998,-0.00552698,-0.00387361,-0.00264539,-0.00103926,-0.00118098,-0.00122822,-0.00198404,-0.00250367,-0.00373189,-0.00368465,-0.00496011,-0.00453496,-0.00533802,-0.00458220,-0.00406257,-0.00231472,-0.00033067,0.00231472,0.00410980,0.00618833,0.00614109,0.00585765,0.00420428,0.00160613,-0.00061411,-0.00368465,-0.00510183,-0.00661348,-0.00637728,-0.00581041,-0.00392085,-0.00184233,0.00037791,0.00160613,0.00269263,0.00155889,0.00141717,-0.00066135,-0.00155889,-0.00382637,-0.00524354,-0.00670796,-0.00869200,-0.00826685,-0.00921163,-0.00713311,-0.00604661,-0.00354294,-0.00174785,0.00080307,0.00193680,0.00420428,0.00354294,0.00420428,0.00188957,0.00051963,-0.00222024,-0.00462944,-0.00623557,-0.00793617,-0.00821961,-0.00803065,-0.00736931,-0.00529078,-0.00410980,-0.00193680,-0.00023620,0.00056687,0.00193680,0.00136993,0.00122822,0.00066135,-0.00094478,-0.00089754,-0.00278711,-0.00245644,-0.00368465,-0.00420428,-0.00448772,-0.00524354,-0.00425152,-0.00377913,-0.00188957,-0.00070859,0.00103926,0.00132270,0.00165337,0.00066135,0.00113374,0.00056687,0.00217300,0.00273987,0.00415704,0.00462944,0.00429876,0.00321226,0.00179509,0.00000000,-0.00165337,-0.00292883,-0.00420428,-0.00481839,-0.00505459,-0.00481839,-0.00415704,-0.00283435,-0.00184233,-0.00023620,0.00023620,0.00070859,0.00061411,0.00028343,0.00037791,0.00014172,0.00066135,0.00155889,0.00207852,0.00330674,0.00349570,0.00401533,0.00382637,0.00406257,0.00330674,0.00311778,0.00118098,-0.00004724,-0.00165337,-0.00188957,-0.00151165,-0.00066135,-0.00118098,-0.00410980,-0.01015641,-0.01686437,-0.02324165,-0.02390300,-0.02007663,-0.01025089,0.00217300,0.01398278,0.02281650,0.02692631,0.02541465,0.01979320,0.01006194,-0.00037791,-0.00958954,-0.01558891,-0.01634474,-0.01374659,-0.00793617,-0.00278711,0.00118098,0.00269263,0.00165337,-0.00033067,-0.00453496,-0.00769998,-0.01214046,-0.01511652,-0.01705333,-0.01757296,-0.01573063,-0.01360487,-0.01010917,-0.00774722,-0.00547974,-0.00519630,-0.00510183,-0.00628280,-0.00647176,-0.00680244,-0.00566870,-0.00429876,-0.00198404,0.00047239,0.00425152,0.00779446,0.01214046,0.01497481,0.01643922,0.01577787,0.01332144,0.00954231,0.00571594,0.00165337,-0.00018896,-0.00240920,-0.00165337,-0.00160613,-0.00018896,0.00070859,0.00155889,0.00165337,0.00174785,0.00051963,-0.00004724,-0.00099202,-0.00174785,-0.00146441,-0.00174785,-0.00108650,-0.00151165,-0.00170061,-0.00236196,-0.00207852,-0.00188957,0.00004724,0.00146441,0.00406257,0.00604661,0.00769998,0.00859752,0.00921163,0.00859752,0.00859752,0.00807789,0.00873924,0.00968402,0.01058157,0.01195150,0.01218770,0.01247113,0.01119567,0.00925887,0.00571594,0.00203128,-0.00207852,-0.00496011,-0.00727483,-0.00869200,-0.00963678,-0.01157359,-0.01303800,-0.01610855,-0.01776191,-0.01903737,-0.01899013,-0.01695885,-0.01502204,-0.01157359,-0.00892820,-0.00562146,-0.00382637,-0.00070859,0.00075583,0.00311778,0.00429876,0.00481839,0.00467667,0.00410980,0.00349570,0.00302330,0.00198404,0.00080307,-0.00127546,-0.00354294,-0.00552698,-0.00684967,-0.00741654,-0.00703863,-0.00628280,-0.00585765,-0.00434600,-0.00477115,-0.00363741,-0.00505459,-0.00514907,-0.00680244,-0.00741654,-0.00840857,-0.00888096,-0.00935335,-0.00958954,-0.01010917,-0.01039261,-0.01110120,-0.01110120,-0.01195150,-0.01185702,-0.01223494,-0.01157359,-0.01105396,-0.01001470,-0.00930611,-0.00878648,-0.00826685,-0.00836133,-0.00788894,-0.00798341,-0.00751102,-0.00788894,-0.00788894,-0.00902267,-0.00940059,-0.01053433,-0.01029813,-0.01029813,-0.00826685,-0.00684967,-0.00406257,-0.00122822,0.00108650,0.00415704,0.00637728,0.00793617,0.00982574,0.01058157,0.01185702,0.01332144,0.01506928,0.01695885,0.01875394,0.01927357,0.01894289,0.01738400,0.01374659,0.01029813,0.00571594,0.00165337,-0.00132270,-0.00368465,-0.00462944,-0.00434600,-0.00467667,-0.00359017,-0.00377913,-0.00368465,-0.00420428,-0.00538526,-0.00703863,-0.00836133,-0.01001470,-0.01058157,-0.01001470,-0.00940059,-0.00798341,-0.00656624,-0.00581041,-0.00410980,-0.00316502,-0.00188957,-0.00103926,-0.00051963,-0.00033067,-0.00037791,-0.00004724,0.00028343,0.00103926,0.00217300,0.00236196,0.00330674,0.00269263,0.00292883,0.00198404,0.00188957,0.00155889,0.00174785,0.00155889,0.00089754,-0.00047239,-0.00245644,-0.00448772,-0.00566870,-0.00642452,-0.00477115,-0.00278711,0.00051963,0.00340122,0.00462944,0.00481839,0.00236196,0.00000000,-0.00311778,-0.00524354,-0.00666072,-0.00821961,-0.00963678,-0.01119567,-0.01270733,-0.01237665,-0.01228218,-0.01034537,-0.00973126,-0.00826685,-0.00855028,-0.00840857,-0.00925887,-0.00982574,-0.01095948,-0.01199874,-0.01313248,-0.01355763,-0.01426622,-0.01355763,-0.01393554,-0.01280181,-0.01303800,-0.01171531,-0.01185702,-0.01034537,-0.01067604,-0.00958954,-0.00935335,-0.00892820,-0.00845581,-0.00788894,-0.00850304,-0.00765274,-0.00779446,-0.00718035,-0.00614109,-0.00576317,-0.00581041,-0.00543250,-0.00713311,-0.00666072,-0.00769998,-0.00718035,-0.00675520,-0.00562146,-0.00505459,-0.00259815,-0.00240920,-0.00056687,-0.00037791,-0.00004724,-0.00033067,0.00004724,-0.00004724,0.00089754,0.00231472,0.00382637,0.00680244,0.00883372,0.01152635,0.01261285,0.01346315,0.01280181,0.01110120,0.00935335,0.00633004,0.00439324,0.00193680,0.00089754,-0.00018896,0.00056687,0.00066135,0.00179509,0.00198404,0.00236196,0.00212576,0.00259815,0.00240920,0.00349570,0.00396809,0.00444048,0.00510183,0.00462944,0.00415704,0.00330674,0.00240920,0.00122822,0.00118098,0.00000000,0.00004724,-0.00047239,-0.00089754,-0.00080307,-0.00099202,-0.00018896,0.00061411,0.00222024,0.00392085,0.00510183,0.00566870,0.00533802,0.00458220,0.00349570,0.00330674,0.00283435,0.00382637,0.00354294,0.00439324,0.00330674,0.00330674,0.00217300,0.00174785,0.00085030,-0.00042515,-0.00160613,-0.00377913,-0.00491287,-0.00599937,-0.00533802,-0.00359017,-0.00118098,0.00198404,0.00359017,0.00510183,0.00382637,0.00240920,-0.00004724,-0.00236196,-0.00420428,-0.00552698,-0.00633004,-0.00585765,-0.00538526,-0.00340122,-0.00188957,0.00070859,0.00245644,0.00481839,0.00599937,0.00647176,0.00557422,0.00259815,-0.00099202,-0.00500735,-0.00769998,-0.00788894,-0.00661348,-0.00330674,0.00009448,0.00273987,0.00481839,0.00462944,0.00401533,0.00184233,-0.00051963,-0.00259815,-0.00387361,-0.00349570,-0.00255091,-0.00033067,0.00103926,0.00136993,0.00113374,-0.00141717,-0.00335398,-0.00581041,-0.00784170,-0.00840857,-0.00892820,-0.00821961,-0.00732207,-0.00604661,-0.00410980,-0.00255091,-0.00047239,0.00061411,0.00222024,0.00288159,0.00429876,0.00524354,0.00562146,0.00576317,0.00420428,0.00255091,0.00051963,-0.00174785,-0.00325950,-0.00444048,-0.00533802,-0.00566870,-0.00576317,-0.00529078,-0.00396809,-0.00245644,0.00000000,0.00141717,0.00349570,0.00396809,0.00420428,0.00335398,0.00250367,0.00085030,0.00051963,-0.00108650,-0.00103926,-0.00170061,-0.00250367,-0.00236196,-0.00340122,-0.00278711,-0.00292883,-0.00222024,-0.00151165,-0.00075583,0.00051963,0.00103926,0.00222024,0.00255091,0.00330674,0.00311778,0.00330674,0.00245644,0.00222024,0.00141717,0.00113374,0.00099202,0.00132270,0.00155889,0.00264539,0.00316502,0.00415704,0.00448772,0.00377913,0.00302330,0.00118098,0.00018896,-0.00127546,-0.00066135,-0.00146441,0.00075583,0.00080307,0.00344846,0.00472391,0.00666072,0.00855028,0.00944783,0.01067604,0.01143187,0.01199874,0.01228218,0.01190426,0.01081776,0.00906991,0.00751102,0.00533802,0.00396809,0.00170061,0.00037791,-0.00113374,-0.00203128,-0.00188957,-0.00108650,-0.00028343,0.00212576,0.00269263,0.00458220,0.00453496,0.00425152,0.00325950,0.00132270,-0.00018896,-0.00245644,-0.00387361,-0.00637728,-0.00732207,-0.00987298,-0.01015641,-0.01124291,-0.01025089,-0.00935335,-0.00684967,-0.00519630,-0.00231472,-0.00066135,0.00085030,0.00155889,0.00122822,0.00042515,-0.00018896,-0.00127546,-0.00094478,-0.00094478,0.00018896,0.00108650,0.00217300,0.00340122,0.00462944,0.00590489,0.00666072,0.00746378,0.00666072,0.00675520,0.00543250,0.00500735,0.00406257,0.00406257,0.00363741,0.00368465,0.00406257,0.00307054,0.00359017,0.00160613,0.00151165,0.00004724,0.00033067,0.00056687,0.00160613,0.00231472,0.00240920,0.00226748,0.00151165,0.00085030,0.00113374,0.00085030,0.00174785,0.00179509,0.00136993,0.00099202,-0.00018896,-0.00070859,-0.00085030,-0.00080307,0.00028343,0.00066135,0.00193680,0.00198404,0.00250367,0.00141717,0.00061411,-0.00085030,-0.00240920,-0.00340122,-0.00448772,-0.00514907,-0.00547974,-0.00533802,-0.00481839,-0.00363741,-0.00193680,-0.00028343,0.00155889,0.00193680,0.00217300,0.00141717,0.00051963,0.00004724,-0.00061411,0.00018896,0.00047239,0.00264539,0.00264539,0.00486563,0.00448772,0.00552698,0.00491287,0.00481839,0.00392085,0.00292883,0.00165337,-0.00014172,-0.00151165,-0.00269263,-0.00368465,-0.00410980,-0.00448772,-0.00444048,-0.00415704,-0.00359017,-0.00363741,-0.00396809,-0.00552698,-0.00746378,-0.00921163,-0.01025089,-0.00944783,-0.00670796,-0.00278711,0.00188957,0.00547974,0.00798341,0.00826685,0.00774722,0.00566870,0.00377913,0.00174785,0.00004724,-0.00103926,-0.00160613,-0.00188957,-0.00122822,-0.00099202,-0.00009448,-0.00014172,0.00023620,0.00000000,0.00056687,0.00113374,0.00184233,0.00222024,0.00269263,0.00236196,0.00273987,0.00288159,0.00354294,0.00444048,0.00477115,0.00529078,0.00429876,0.00373189,0.00259815,0.00141717,0.00160613,0.00122822,0.00151165,0.00141717,0.00085030,0.00037791,-0.00094478,-0.00155889,-0.00297607,-0.00354294,-0.00406257,-0.00382637,-0.00255091,-0.00170061,0.00108650,0.00222024,0.00458220,0.00533802,0.00656624,0.00651900,0.00694415,0.00628280,0.00505459,0.00396809,0.00198404,0.00127546,0.00146441,0.00283435,0.00566870,0.00784170,0.00977850,0.00935335,0.00793617,0.00500735,0.00240920,0.00018896,-0.00037791,-0.00099202,-0.00009448,0.00014172,0.00066135,0.00075583,0.00061411,0.00000000,-0.00028343,-0.00051963,0.00000000,0.00132270,0.00250367,0.00481839,0.00557422,0.00680244,0.00661348,0.00651900,0.00566870,0.00529078,0.00425152,0.00420428,0.00321226,0.00321226,0.00212576,0.00160613,0.00056687,-0.00023620,-0.00037791,-0.00033067,0.00085030,0.00240920,0.00420428,0.00670796,0.00869200,0.01086500,0.01199874,0.01237665,0.01119567,0.00992022,0.00741654,0.00571594,0.00392085,0.00311778,0.00222024,0.00311778,0.00273987,0.00462944,0.00439324,0.00581041,0.00462944,0.00481839,0.00344846,0.00344846,0.00344846,0.00415704,0.00519630,0.00642452,0.00708587,0.00741654,0.00708587,0.00670796,0.00538526,0.00467667,0.00321226,0.00250367,0.00160613,0.00174785,0.00198404,0.00302330,0.00359017,0.00330674,0.00170061,-0.00051963,-0.00392085,-0.00604661,-0.00798341,-0.00821961,-0.00689691,-0.00524354,-0.00344846,-0.00170061,-0.00151165,-0.00118098,-0.00122822,-0.00226748,-0.00151165,-0.00269263,-0.00170061,-0.00231472,-0.00151165,-0.00170061,-0.00094478,-0.00080307,0.00056687,0.00141717,0.00340122,0.00533802,0.00684967,0.00864476,0.00878648,0.00836133,0.00708587,0.00514907,0.00325950,0.00174785,0.00004724,-0.00075583,-0.00174785,-0.00174785,-0.00179509,-0.00033067,0.00056687,0.00240920,0.00344846,0.00434600,0.00481839,0.00458220,0.00439324,0.00335398,0.00302330,0.00226748,0.00207852,0.00160613,0.00132270,0.00023620,-0.00042515,-0.00212576,-0.00311778,-0.00444048,-0.00543250,-0.00599937,-0.00722759,-0.00675520,-0.00751102,-0.00566870,-0.00401533,-0.00146441,0.00127546,0.00250367,0.00316502,0.00188957,0.00051963,-0.00132270,-0.00236196,-0.00297607,-0.00344846,-0.00330674,-0.00373189,-0.00292883,-0.00273987,-0.00122822,0.00023620,0.00099202,0.00217300,0.00170061,0.00184233,0.00136993,0.00051963,-0.00004724,-0.00127546,-0.00203128,-0.00250367,-0.00217300,-0.00141717,0.00075583,0.00207852,0.00410980,0.00472391,0.00481839,0.00368465,0.00245644,0.00033067,-0.00037791,-0.00141717,-0.00103926,0.00000000,0.00151165,0.00321226,0.00500735,0.00637728,0.00718035,0.00788894,0.00746378,0.00699139,0.00656624,0.00599937,0.00604661,0.00647176,0.00713311,0.00741654,0.00817237,0.00718035,0.00647176,0.00425152,0.00184233,0.00070859,0.00061411,0.00377913,0.00803065,0.01421898,0.01969872,0.02314718,0.02494226,0.02239135,0.01922633,0.01294352,0.00751102,0.00217300,-0.00136993,-0.00359017,-0.00420428,-0.00448772,-0.00387361,-0.00330674,-0.00217300,-0.00056687,0.00122822,0.00311778,0.00458220,0.00571594,0.00670796,0.00623557,0.00684967,0.00595213,0.00614109,0.00571594,0.00576317,0.00585765,0.00609385,0.00590489,0.00562146,0.00434600,0.00325950,0.00118098,-0.00070859,-0.00188957,-0.00321226,-0.00184233,-0.00132270,0.00047239,0.00203128,0.00250367,0.00344846,0.00330674,0.00368465,0.00363741,0.00448772,0.00439324,0.00533802,0.00529078,0.00514907,0.00472391,0.00349570,0.00184233,-0.00004724,-0.00179509,-0.00363741,-0.00448772,-0.00519630,-0.00547974,-0.00477115,-0.00429876,-0.00250367,-0.00108650,0.00160613,0.00278711,0.00529078,0.00566870,0.00680244,0.00614109,0.00529078,0.00410980,0.00198404,0.00037791,-0.00160613,-0.00363741,-0.00510183,-0.00628280,-0.00651900,-0.00547974,-0.00448772,-0.00184233,-0.00070859,0.00160613,0.00212576,0.00203128,0.00217300,0.00018896,0.00028343,-0.00179509,-0.00174785,-0.00236196,-0.00236196,-0.00203128,-0.00231472,-0.00217300,-0.00278711,-0.00273987,-0.00316502,-0.00259815,-0.00297607,-0.00198404,-0.00245644,-0.00146441,-0.00198404,-0.00056687,-0.00047239,0.00094478,0.00141717,0.00174785,0.00226748,0.00146441,0.00184233,0.00179509,0.00193680,0.00325950,0.00264539,0.00363741,0.00245644,0.00259815,0.00184233,0.00269263,0.00344846,0.00510183,0.00661348,0.00788894,0.00878648,0.00906991,0.00888096,0.00821961,0.00718035,0.00623557,0.00505459,0.00429876,0.00382637,0.00406257,0.00462944,0.00618833,0.00703863,0.00821961,0.00836133,0.00859752,0.00812513,0.00840857,0.00812513,0.00897544,0.00859752,0.00902267,0.00831409,0.00831409,0.00821961,0.00821961,0.00845581,0.00850304,0.00821961,0.00788894,0.00727483,0.00699139,0.00642452,0.00595213,0.00529078,0.00439324,0.00373189,0.00264539,0.00184233,0.00085030,0.00085030,0.00099202,0.00245644,0.00415704,0.00595213,0.00751102,0.00793617,0.00793617,0.00642452,0.00491287,0.00222024,0.00023620,-0.00222024,-0.00316502,-0.00382637,-0.00340122,-0.00288159,-0.00255091,-0.00236196,-0.00250367,-0.00273987,-0.00255091,-0.00321226,-0.00273987,-0.00373189,-0.00349570,-0.00406257,-0.00401533,-0.00359017,-0.00429876,-0.00401533,-0.00529078,-0.00609385,-0.00689691,-0.00741654,-0.00699139,-0.00642452,-0.00581041,-0.00491287,-0.00557422,-0.00514907,-0.00633004,-0.00599937,-0.00614109,-0.00543250,-0.00448772,-0.00444048,-0.00335398,-0.00429876,-0.00349570,-0.00420428,-0.00444048,-0.00453496,-0.00496011,-0.00529078,-0.00505459,-0.00519630,-0.00377913,-0.00278711,-0.00085030,0.00037791,0.00146441,0.00146441,0.00141717,0.00141717,0.00193680,0.00406257,0.00557422,0.00751102,0.00798341,0.00746378,0.00618833,0.00439324,0.00193680,-0.00028343,-0.00278711,-0.00458220,-0.00510183,-0.00425152,-0.00141717,0.00136993,0.00420428,0.00595213,0.00486563,0.00415704,0.00127546,0.00033067,-0.00037791,0.00042515,0.00151165,0.00269263,0.00278711,0.00188957,0.00000000,-0.00184233,-0.00316502,-0.00340122,-0.00250367,-0.00099202,0.00037791,0.00122822,0.00184233,0.00136993,0.00066135,0.00000000,-0.00146441,-0.00179509,-0.00231472,-0.00222024,-0.00108650,-0.00037791,0.00108650,0.00132270,0.00207852,0.00165337,0.00136993,0.00056687,-0.00009448,-0.00094478,-0.00198404,-0.00188957,-0.00273987,-0.00155889,-0.00108650,0.00051963,0.00198404,0.00330674,0.00368465,0.00425152,0.00325950,0.00311778,0.00188957,0.00113374,-0.00009448,-0.00132270,-0.00255091,-0.00396809,-0.00514907,-0.00647176,-0.00722759,-0.00840857,-0.00803065,-0.00892820,-0.00746378,-0.00703863,-0.00571594,-0.00406257,-0.00359017,-0.00222024,-0.00222024,-0.00174785,-0.00179509,-0.00184233,-0.00188957,-0.00170061,-0.00179509,-0.00132270,-0.00113374,-0.00070859,-0.00004724,0.00047239,0.00094478,0.00103926,0.00047239,-0.00014172,-0.00103926,-0.00118098,-0.00070859,0.00014172,0.00136993,0.00160613,0.00174785,0.00023620,-0.00099202,-0.00250367,-0.00354294,-0.00330674,-0.00368465,-0.00288159,-0.00349570,-0.00368465,-0.00444048,-0.00500735,-0.00491287,-0.00434600,-0.00307054,-0.00179509,-0.00099202,-0.00037791,-0.00136993,-0.00160613,-0.00354294,-0.00382637,-0.00481839,-0.00425152,-0.00434600,-0.00349570,-0.00292883,-0.00259815,-0.00207852,-0.00245644,-0.00292883,-0.00377913,-0.00467667,-0.00566870,-0.00552698,-0.00562146,-0.00524354,-0.00458220,-0.00510183,-0.00496011,-0.00581041,-0.00562146,-0.00547974,-0.00510183,-0.00401533,-0.00377913,-0.00273987,-0.00307054,-0.00325950,-0.00467667,-0.00609385,-0.00845581,-0.00949507,-0.01077052,-0.01058157,-0.01015641,-0.00911715,-0.00788894,-0.00689691,-0.00618833,-0.00524354,-0.00462944,-0.00377913,-0.00344846,-0.00302330,-0.00273987,-0.00340122,-0.00273987,-0.00373189,-0.00259815,-0.00245644,-0.00141717,-0.00089754,0.00028343,0.00028343,0.00118098,0.00132270,0.00132270,0.00080307,-0.00004724,-0.00127546,-0.00184233,-0.00245644,-0.00184233,-0.00118098,-0.00037791,0.00070859,0.00103926,0.00165337,0.00118098,0.00070859,-0.00070859,-0.00212576,-0.00363741,-0.00458220,-0.00529078,-0.00566870,-0.00576317,-0.00623557,-0.00576317,-0.00647176,-0.00566870,-0.00566870,-0.00500735,-0.00387361,-0.00297607,-0.00118098,0.00033067,0.00203128,0.00292883,0.00415704,0.00382637,0.00316502,0.00174785,-0.00028343,-0.00207852,-0.00297607,-0.00354294,-0.00278711,-0.00174785,-0.00033067,0.00061411,0.00085030,0.00061411,-0.00094478,-0.00212576,-0.00420428,-0.00510183,-0.00604661,-0.00566870,-0.00562146,-0.00472391,-0.00420428,-0.00330674,-0.00231472,-0.00141717,-0.00066135,-0.00066135,-0.00085030,-0.00198404,-0.00240920,-0.00344846,-0.00354294,-0.00349570,-0.00321226,-0.00273987,-0.00141717,-0.00094478,0.00089754,0.00108650,0.00184233,0.00103926,0.00033067,-0.00094478,-0.00212576,-0.00240920,-0.00259815,-0.00170061,-0.00066135,-0.00004724,0.00155889,0.00222024,0.00382637,0.00496011,0.00552698,0.00637728,0.00510183,0.00472391,0.00155889,-0.00014172,-0.00311778,-0.00458220,-0.00458220,-0.00335398,-0.00066135,0.00278711,0.00510183,0.00751102,0.00798341,0.00708587,0.00571594,0.00269263,0.00023620,-0.00259815,-0.00420428,-0.00472391,-0.00434600,-0.00288159,-0.00217300,-0.00155889,-0.00193680,-0.00292883,-0.00377913,-0.00444048,-0.00444048,-0.00382637,-0.00250367,-0.00132270,0.00094478,0.00203128,0.00434600,0.00500735,0.00684967,0.00628280,0.00651900,0.00491287,0.00382637,0.00269263,0.00155889,0.00226748,0.00273987,0.00562146,0.00727483,0.00906991,0.00973126,0.00855028,0.00694415,0.00462944,0.00321226,0.00311778,0.00429876,0.00604661,0.00788894,0.00850304,0.00869200,0.00703863,0.00581041,0.00259815,0.00080307,-0.00264539,-0.00368465,-0.00562146,-0.00500735,-0.00439324,-0.00217300,0.00033067,0.00226748,0.00415704,0.00377913,0.00264539,0.00018896,-0.00349570,-0.00552698,-0.00850304,-0.00892820,-0.00977850,-0.00921163,-0.00850304,-0.00793617,-0.00708587,-0.00703863,-0.00694415,-0.00699139,-0.00746378,-0.00675520,-0.00623557,-0.00453496,-0.00311778,-0.00127546,-0.00028343,0.00160613,0.00165337,0.00316502,0.00297607,0.00420428,0.00415704,0.00462944,0.00481839,0.00415704,0.00410980,0.00325950,0.00269263,0.00240920,0.00179509,0.00127546,0.00118098,0.00037791,0.00042515,0.00018896,0.00004724,0.00018896,0.00009448,0.00009448,0.00018896,0.00028343,0.00014172,0.00061411,0.00085030,0.00132270,0.00212576,0.00198404,0.00273987,0.00250367,0.00330674,0.00344846,0.00377913,0.00373189,0.00264539,0.00207852,0.00061411,0.00033067,0.00009448,0.00033067,0.00033067,0.00080307,0.00004724,0.00061411,-0.00047239,-0.00056687,-0.00226748,-0.00311778,-0.00486563,-0.00510183,-0.00557422,-0.00425152,-0.00368465,-0.00099202,-0.00070859,0.00184233,0.00203128,0.00292883,0.00311778,0.00207852,0.00089754,-0.00080307,-0.00302330,-0.00439324,-0.00562146,-0.00581041,-0.00519630,-0.00481839,-0.00354294,-0.00340122,-0.00273987,-0.00250367,-0.00184233,-0.00132270,-0.00042515,-0.00061411,-0.00009448,-0.00066135,-0.00061411,-0.00066135,-0.00028343,-0.00004724,0.00004724,-0.00047239,-0.00118098,-0.00188957,-0.00273987,-0.00236196,-0.00203128,-0.00042515,0.00136993,0.00330674,0.00500735,0.00581041,0.00557422,0.00458220,0.00203128,0.00037791,-0.00273987,-0.00373189,-0.00557422,-0.00585765,-0.00529078,-0.00477115,-0.00302330,-0.00207852,-0.00170061,-0.00203128,-0.00363741,-0.00614109,-0.00741654,-0.00906991,-0.00888096,-0.00869200,-0.00779446,-0.00769998,-0.00722759,-0.00760550,-0.00751102,-0.00751102,-0.00699139,-0.00656624,-0.00524354,-0.00425152,-0.00222024,-0.00047239,0.00198404,0.00325950,0.00439324,0.00420428,0.00340122,0.00255091,0.00165337,0.00170061,0.00203128,0.00278711,0.00240920,0.00236196,0.00089754,0.00051963,-0.00051963,0.00056687,0.00094478,0.00354294,0.00458220,0.00604661,0.00618833,0.00538526,0.00387361,0.00188957,0.00037791,-0.00108650,-0.00122822,-0.00165337,-0.00037791,-0.00018896,0.00108650,0.00146441,0.00165337,0.00136993,0.00033067,-0.00127546,-0.00245644,-0.00387361,-0.00444048,-0.00406257,-0.00396809,-0.00207852,-0.00151165,-0.00018896,0.00004724,-0.00014172,-0.00136993,-0.00259815,-0.00444048,-0.00609385,-0.00722759,-0.00869200,-0.00869200,-0.00930611,-0.00826685,-0.00746378,-0.00552698,-0.00330674,-0.00085030,0.00103926,0.00288159,0.00297607,0.00297607,0.00165337,-0.00004724,-0.00170061,-0.00354294,-0.00359017,-0.00377913,-0.00198404,-0.00014172,0.00222024,0.00434600,0.00595213,0.00614109,0.00614109,0.00458220,0.00325950,0.00122822,0.00028343,-0.00089754,-0.00094478,-0.00127546,-0.00132270,-0.00188957,-0.00264539,-0.00387361,-0.00496011,-0.00552698,-0.00585765,-0.00514907,-0.00410980,-0.00198404,-0.00033067,0.00259815,0.00325950,0.00524354,0.00425152,0.00444048,0.00259815,0.00203128,0.00103926,0.00099202,0.00061411,0.00051963,-0.00037791,-0.00070859,-0.00217300,-0.00250367,-0.00311778,-0.00330674,-0.00316502,-0.00316502,-0.00278711,-0.00278711,-0.00236196,-0.00250367,-0.00236196,-0.00307054,-0.00264539,-0.00316502,-0.00193680,-0.00155889,-0.00061411,-0.00033067,-0.00028343,-0.00122822,-0.00193680,-0.00288159,-0.00325950,-0.00288159,-0.00222024,-0.00118098,-0.00028343,0.00009448,0.00004724,0.00018896,-0.00075583,-0.00066135,-0.00207852,-0.00245644,-0.00458220,-0.00557422,-0.00732207,-0.00689691,-0.00614109,-0.00363741,-0.00094478,0.00174785,0.00401533,0.00524354,0.00609385,0.00604661,0.00618833,0.00514907,0.00491287,0.00302330,0.00311778,0.00151165,0.00250367,0.00325950,0.00529078,0.00774722,0.01010917,0.01247113,0.01426622,0.01539996,0.01577787,0.01459689,0.01336868,0.00982574,0.00803065,0.00425152,0.00297607,0.00132270,0.00056687,0.00089754,0.00018896,0.00179509,0.00203128,0.00467667,0.00647176,0.00906991,0.01048709,0.01147911,0.01034537,0.00944783,0.00618833,0.00425152,0.00099202,-0.00018896,-0.00193680,-0.00160613,-0.00155889,-0.00061411,0.00047239,0.00127546,0.00174785,0.00231472,0.00160613,0.00174785,0.00108650,0.00075583,0.00108650,0.00066135,0.00066135,0.00000000,-0.00099202,-0.00203128,-0.00236196,-0.00297607,-0.00207852,-0.00160613,-0.00056687,0.00099202,0.00122822,0.00297607,0.00245644,0.00283435,0.00217300,0.00103926,0.00037791,-0.00018896,-0.00037791,-0.00014172,0.00018896,0.00014172,0.00047239,0.00028343,-0.00004724,-0.00009448,-0.00066135,-0.00042515,-0.00089754,-0.00028343,-0.00037791,0.00089754,0.00089754,0.00151165,0.00042515,-0.00099202,-0.00307054,-0.00486563,-0.00481839,-0.00406257,-0.00089754,0.00203128,0.00481839,0.00623557,0.00590489,0.00420428,0.00160613,-0.00222024,-0.00529078,-0.00940059,-0.01091224,-0.01242389,-0.01129015,-0.00897544,-0.00656624,-0.00382637,-0.00193680,-0.00151165,-0.00122822,-0.00184233,-0.00259815,-0.00283435,-0.00297607,-0.00302330,-0.00188957,-0.00160613,-0.00028343,0.00061411,0.00165337,0.00264539,0.00363741,0.00373189,0.00429876,0.00396809,0.00325950,0.00288159,0.00089754,-0.00037791,-0.00288159,-0.00524354,-0.00727483,-0.00911715,-0.00925887,-0.00949507,-0.00803065,-0.00736931,-0.00514907,-0.00491287,-0.00307054,-0.00344846,-0.00269263,-0.00307054,-0.00340122,-0.00486563,-0.00585765,-0.00784170,-0.00840857,-0.00916439,-0.00817237,-0.00718035,-0.00514907,-0.00444048,-0.00406257,-0.00462944,-0.00590489,-0.00637728,-0.00760550,-0.00722759,-0.00694415,-0.00642452,-0.00533802,-0.00500735,-0.00444048,-0.00382637,-0.00392085,-0.00297607,-0.00255091,-0.00070859,0.00018896,0.00203128,0.00217300,0.00222024,0.00103926,0.00023620,-0.00070859,-0.00051963,-0.00004724,0.00047239,0.00146441,0.00122822,0.00132270,0.00042515,0.00028343,-0.00047239,0.00000000,-0.00014172,0.00075583,0.00085030,0.00122822,0.00080307,0.00103926,0.00047239,0.00051963,0.00056687,0.00037791,0.00122822,0.00141717,0.00297607,0.00396809,0.00562146,0.00628280,0.00670796,0.00562146,0.00462944,0.00307054,0.00155889,0.00122822,0.00066135,0.00207852,0.00311778,0.00505459,0.00708587,0.00803065,0.00878648,0.00784170,0.00585765,0.00396809,0.00089754,-0.00085030,-0.00311778,-0.00434600,-0.00566870,-0.00656624,-0.00689691,-0.00708587,-0.00647176,-0.00514907,-0.00415704,-0.00207852,-0.00113374,0.00061411,0.00174785,0.00302330,0.00392085,0.00448772,0.00392085,0.00297607,0.00160613,0.00023620,0.00037791,0.00028343,0.00179509,0.00359017,0.00467667,0.00675520,0.00618833,0.00618833,0.00425152,0.00184233,-0.00099202,-0.00406257,-0.00651900,-0.00836133,-0.00892820,-0.00892820,-0.00699139,-0.00519630,-0.00193680,0.00047239,0.00292883,0.00406257,0.00467667,0.00392085,0.00354294,0.00170061,0.00089754,-0.00051963,-0.00151165,-0.00231472,-0.00292883,-0.00283435,-0.00217300,-0.00080307,0.00136993,0.00387361,0.00666072,0.00906991,0.01058157,0.01072328,0.00973126,0.00769998,0.00500735,0.00321226,0.00122822,0.00061411,0.00047239,0.00047239,0.00033067,0.00047239,-0.00047239,-0.00042515,-0.00165337,-0.00146441,-0.00240920,-0.00184233,-0.00207852,-0.00165337,-0.00103926,-0.00122822,-0.00085030,-0.00108650,-0.00061411,0.00047239,0.00184233,0.00415704,0.00557422,0.00769998,0.00793617,0.00793617,0.00666072,0.00458220,0.00273987,0.00085030,-0.00009448,0.00023620,0.00108650,0.00231472,0.00344846,0.00363741,0.00387361,0.00325950,0.00368465,0.00340122,0.00448772,0.00439324,0.00472391,0.00377913,0.00297607,0.00174785,0.00080307,0.00018896,0.00051963,0.00127546,0.00273987,0.00425152,0.00529078,0.00666072,0.00694415,0.00746378,0.00722759,0.00727483,0.00656624,0.00656624,0.00529078,0.00552698,0.00496011,0.00566870,0.00661348,0.00765274,0.00973126,0.01006194,0.01162083,0.01025089,0.00949507,0.00670796,0.00410980,0.00051963,-0.00170061,-0.00330674,-0.00387361,-0.00250367,-0.00174785,0.00094478,0.00174785,0.00368465,0.00363741,0.00382637,0.00307054,0.00188957,0.00103926,0.00028343,0.00000000,0.00033067,0.00127546,0.00236196,0.00387361,0.00444048,0.00491287,0.00491287,0.00472391,0.00448772,0.00429876,0.00401533,0.00349570,0.00292883,0.00155889,0.00146441,0.00070859,0.00113374,0.00193680,0.00193680,0.00255091,0.00255091,0.00269263,0.00288159,0.00335398,0.00363741,0.00444048,0.00519630,0.00590489,0.00680244,0.00755826,0.00788894,0.00883372,0.00892820,0.01039261,0.01067604,0.01180978,0.01162083,0.01171531,0.01067604,0.00925887,0.00769998,0.00590489,0.00415704,0.00330674,0.00174785,0.00146441,0.00066135,0.00014172,-0.00047239,-0.00198404,-0.00222024,-0.00392085,-0.00392085,-0.00500735,-0.00481839,-0.00458220,-0.00425152,-0.00359017,-0.00340122,-0.00269263,-0.00259815,-0.00203128,-0.00151165,-0.00146441,-0.00066135,-0.00103926,-0.00042515,-0.00028343,0.00000000,-0.00037791,-0.00085030,-0.00207852,-0.00292883,-0.00325950,-0.00283435,-0.00122822,0.00033067,0.00217300,0.00240920,0.00269263,0.00122822,0.00009448,-0.00108650,-0.00231472,-0.00198404,-0.00174785,-0.00070859,0.00070859,0.00118098,0.00236196,0.00179509,0.00203128,0.00141717,0.00070859,0.00099202,-0.00028343,0.00009448,-0.00037791,-0.00004724,0.00061411,0.00103926,0.00118098,0.00132270,0.00042515,-0.00014172,-0.00089754,-0.00141717,-0.00165337,-0.00099202,-0.00103926,-0.00009448,-0.00047239,-0.00033067,-0.00118098,-0.00179509,-0.00269263,-0.00311778,-0.00335398,-0.00278711,-0.00217300,-0.00141717,-0.00066135,-0.00056687,-0.00047239,-0.00070859,-0.00151165,-0.00184233,-0.00321226,-0.00335398,-0.00481839,-0.00429876,-0.00434600,-0.00302330,-0.00155889,0.00014172,0.00226748,0.00377913,0.00519630,0.00571594,0.00529078,0.00387361,0.00174785,-0.00061411,-0.00273987,-0.00368465,-0.00401533,-0.00255091,-0.00160613,-0.00009448,0.00066135,0.00103926,0.00113374,0.00099202,0.00080307,0.00028343,0.00033067,-0.00028343,-0.00004724,-0.00009448,0.00047239,0.00085030,0.00193680,0.00273987,0.00373189,0.00458220,0.00472391,0.00467667,0.00377913,0.00340122,0.00193680,0.00250367,0.00122822,0.00193680,0.00108650,0.00094478,0.00042515,-0.00037791,-0.00075583,-0.00155889,-0.00231472,-0.00325950,-0.00444048,-0.00491287,-0.00557422,-0.00491287,-0.00462944,-0.00340122,-0.00259815,-0.00174785,-0.00127546,-0.00108650,-0.00042515,0.00018896,0.00070859,0.00203128,0.00174785,0.00245644,0.00146441,0.00103926,-0.00009448,-0.00127546,-0.00207852,-0.00311778,-0.00307054,-0.00344846,-0.00283435,-0.00321226,-0.00316502,-0.00377913,-0.00486563,-0.00514907,-0.00628280,-0.00566870,-0.00514907,-0.00420428,-0.00236196,-0.00165337,-0.00028343,-0.00009448,0.00094478,0.00108650,0.00217300,0.00302330,0.00377913,0.00524354,0.00514907,0.00604661,0.00519630,0.00538526,0.00444048,0.00434600,0.00429876,0.00415704,0.00429876,0.00349570,0.00231472,0.00051963,-0.00151165,-0.00307054,-0.00467667,-0.00538526,-0.00604661,-0.00604661,-0.00524354,-0.00444048,-0.00255091,-0.00141717,0.00080307,0.00122822,0.00283435,0.00226748,0.00288159,0.00207852,0.00231472,0.00165337,0.00179509,0.00127546,0.00070859,-0.00009448,-0.00099202,-0.00198404,-0.00283435,-0.00307054,-0.00363741,-0.00292883,-0.00302330,-0.00198404,-0.00188957,-0.00136993,-0.00146441,-0.00188957,-0.00236196,-0.00297607,-0.00359017,-0.00316502,-0.00316502,-0.00212576,-0.00151165,-0.00089754,-0.00018896,-0.00051963,-0.00004724,0.00009448,0.00070859,0.00179509,0.00269263,0.00302330,0.00349570,0.00207852,0.00122822,-0.00085030,-0.00179509,-0.00259815,-0.00179509,-0.00089754,0.00056687,0.00146441,0.00113374,0.00004724,-0.00170061,-0.00359017,-0.00458220,-0.00505459,-0.00425152,-0.00359017,-0.00170061,-0.00118098,0.00000000,-0.00018896,-0.00042515,-0.00146441,-0.00259815,-0.00340122,-0.00453496,-0.00467667,-0.00538526,-0.00571594,-0.00529078,-0.00519630,-0.00429876,-0.00307054,-0.00207852,-0.00066135,0.00037791,0.00146441,0.00212576,0.00302330,0.00264539,0.00273987,0.00122822,0.00009448,-0.00273987,-0.00444048,-0.00727483,-0.00869200,-0.01001470,-0.01072328,-0.01020365,-0.01010917,-0.00864476,-0.00751102,-0.00604661,-0.00439324,-0.00325950,-0.00179509,-0.00118098,-0.00028343,-0.00028343,-0.00014172,-0.00075583,-0.00118098,-0.00231472,-0.00288159,-0.00406257,-0.00444048,-0.00458220,-0.00406257,-0.00330674,-0.00203128,-0.00155889,-0.00089754,-0.00094478,-0.00155889,-0.00132270,-0.00179509,-0.00099202,-0.00061411,0.00000000,0.00004724,0.00009448,0.00000000,-0.00042515,-0.00023620,0.00009448,-0.00028343,0.00051963,0.00000000,0.00023620,0.00018896,-0.00047239,-0.00028343,-0.00146441,-0.00141717,-0.00240920,-0.00236196,-0.00217300,-0.00231472,-0.00212576,-0.00245644,-0.00259815,-0.00278711,-0.00325950,-0.00330674,-0.00363741,-0.00373189,-0.00453496,-0.00439324,-0.00510183,-0.00410980,-0.00368465,-0.00269263,-0.00118098,-0.00047239,0.00033067,0.00037791,0.00004724,-0.00089754,-0.00136993,-0.00264539,-0.00273987,-0.00330674,-0.00359017,-0.00330674,-0.00349570,-0.00231472,-0.00146441,0.00070859,0.00198404,0.00373189,0.00410980,0.00387361,0.00264539,0.00047239,-0.00198404,-0.00444048,-0.00585765,-0.00689691,-0.00628280,-0.00496011,-0.00269263,0.00000000,0.00231472,0.00429876,0.00566870,0.00552698,0.00524354,0.00401533,0.00340122,0.00292883,0.00373189,0.00434600,0.00566870,0.00666072,0.00637728,0.00699139,0.00557422,0.00519630,0.00406257,0.00264539,0.00179509,0.00000000,-0.00089754,-0.00217300,-0.00321226,-0.00354294,-0.00453496,-0.00434600,-0.00462944,-0.00505459,-0.00552698,-0.00595213,-0.00585765,-0.00524354,-0.00354294,-0.00151165,0.00033067,0.00278711,0.00283435,0.00297607,0.00089754,-0.00127546,-0.00406257,-0.00566870,-0.00708587,-0.00599937,-0.00519630,-0.00288159,-0.00118098,0.00070859,0.00188957,0.00269263,0.00269263,0.00198404,0.00113374,-0.00014172,-0.00089754,-0.00146441,-0.00127546,-0.00127546,-0.00099202,-0.00113374,-0.00146441,-0.00184233,-0.00212576,-0.00255091,-0.00226748,-0.00193680,-0.00132270,-0.00004724,0.00127546,0.00255091,0.00302330,0.00292883,0.00165337,0.00023620,-0.00141717,-0.00250367,-0.00269263,-0.00245644,-0.00155889,-0.00089754,-0.00023620,-0.00004724,-0.00033067,-0.00061411,-0.00070859,-0.00108650,-0.00066135,-0.00028343,0.00094478,0.00217300,0.00311778,0.00410980,0.00387361,0.00354294,0.00217300,0.00066135,-0.00018896,-0.00103926,-0.00094478,-0.00118098,-0.00122822,-0.00136993,-0.00231472,-0.00222024,-0.00368465,-0.00311778,-0.00477115,-0.00439324,-0.00590489,-0.00571594,-0.00708587,-0.00656624,-0.00807789,-0.00699139,-0.00798341,-0.00661348,-0.00614109,-0.00434600,-0.00302330,-0.00118098,-0.00042515,0.00033067,0.00056687,0.00037791,0.00066135,0.00047239,0.00080307,0.00113374,0.00151165,0.00212576,0.00311778,0.00349570,0.00505459,0.00467667,0.00585765,0.00472391,0.00429876,0.00297607,0.00141717,0.00018896,-0.00103926,-0.00141717,-0.00269263,-0.00226748,-0.00354294,-0.00321226,-0.00410980,-0.00387361,-0.00415704,-0.00316502,-0.00245644,-0.00075583,0.00023620,0.00222024,0.00212576,0.00288159,0.00089754,0.00023620,-0.00240920,-0.00316502,-0.00434600,-0.00420428,-0.00363741,-0.00292883,-0.00174785,-0.00108650,-0.00056687,0.00028343,-0.00037791,0.00108650,-0.00014172,0.00085030,0.00033067,0.00047239,0.00061411,0.00089754,0.00094478,0.00184233,0.00132270,0.00217300,0.00179509,0.00179509,0.00165337,0.00132270,0.00099202,0.00146441,0.00103926,0.00179509,0.00155889,0.00146441,0.00066135,0.00009448,-0.00127546,-0.00188957,-0.00307054,-0.00373189,-0.00410980,-0.00444048,-0.00415704,-0.00359017,-0.00288159,-0.00136993,0.00051963,0.00297607,0.00585765,0.00869200,0.01053433,0.01157359,0.01086500,0.00859752,0.00609385,0.00278711,0.00047239,-0.00094478,-0.00193680,-0.00155889,-0.00155889,-0.00080307,-0.00080307,-0.00033067,-0.00089754,-0.00056687,-0.00212576,-0.00160613,-0.00307054,-0.00207852,-0.00273987,-0.00236196,-0.00292883,-0.00406257,-0.00481839,-0.00623557,-0.00633004,-0.00595213,-0.00415704,-0.00245644,0.00014172,0.00132270,0.00255091,0.00255091,0.00236196,0.00207852,0.00259815,0.00330674,0.00519630,0.00651900,0.00807789,0.00883372,0.00878648,0.00949507,0.00803065,0.00873924,0.00675520,0.00618833,0.00420428,0.00283435,0.00132270,-0.00009448,-0.00085030,-0.00174785,-0.00198404,-0.00222024,-0.00212576,-0.00203128,-0.00151165,-0.00170061,-0.00108650,-0.00174785,-0.00103926,-0.00108650,-0.00023620,0.00009448,0.00009448,-0.00047239,-0.00174785,-0.00368465,-0.00519630,-0.00675520,-0.00741654,-0.00718035,-0.00713311,-0.00547974,-0.00477115,-0.00321226,-0.00222024,-0.00170061,-0.00132270,-0.00207852,-0.00330674,-0.00425152,-0.00618833,-0.00689691,-0.00755826,-0.00784170,-0.00722759,-0.00732207,-0.00647176,-0.00680244,-0.00618833,-0.00703863,-0.00670796,-0.00718035,-0.00680244,-0.00661348,-0.00533802,-0.00514907,-0.00292883,-0.00292883,-0.00103926,-0.00075583,0.00018896,0.00037791,0.00028343,-0.00061411,-0.00165337,-0.00335398,-0.00382637,-0.00458220,-0.00368465,-0.00222024,-0.00075583,0.00113374,0.00240920,0.00292883,0.00325950,0.00245644,0.00113374,-0.00023620,-0.00188957,-0.00354294,-0.00472391,-0.00581041,-0.00609385,-0.00599937,-0.00529078,-0.00425152,-0.00302330,-0.00165337,-0.00033067,0.00023620,0.00170061,0.00127546,0.00250367,0.00207852,0.00240920,0.00226748,0.00212576,0.00160613,0.00188957,0.00127546,0.00146441,0.00160613,0.00127546,0.00155889,0.00108650,0.00061411,0.00023620,-0.00028343,-0.00009448,0.00028343,0.00094478,0.00207852,0.00207852,0.00278711,0.00193680,0.00127546,-0.00033067,-0.00179509,-0.00377913,-0.00500735,-0.00637728,-0.00722759,-0.00760550,-0.00774722,-0.00736931,-0.00647176,-0.00533802,-0.00387361,-0.00231472,-0.00103926,0.00033067,0.00066135,0.00085030,-0.00018896,-0.00122822,-0.00278711,-0.00410980,-0.00510183,-0.00590489,-0.00552698,-0.00562146,-0.00467667,-0.00434600,-0.00349570,-0.00325950,-0.00321226,-0.00387361,-0.00448772,-0.00500735,-0.00505459,-0.00406257,-0.00269263,0.00033067,0.00212576,0.00500735,0.00599937,0.00703863,0.00623557,0.00533802,0.00316502,0.00136993,-0.00080307,-0.00245644,-0.00316502,-0.00392085,-0.00363741,-0.00349570,-0.00373189,-0.00349570,-0.00420428,-0.00406257,-0.00396809,-0.00297607,-0.00250367,-0.00061411,-0.00132270,0.00018896,-0.00146441,-0.00151165,-0.00288159,-0.00392085,-0.00477115,-0.00514907,-0.00543250,-0.00458220,-0.00434600,-0.00368465,-0.00401533,-0.00429876,-0.00519630,-0.00604661,-0.00623557,-0.00614109,-0.00552698,-0.00368465,-0.00240920,0.00009448,0.00155889,0.00292883,0.00368465,0.00288159,0.00250367,0.00070859,-0.00051963,-0.00207852,-0.00297607,-0.00387361,-0.00330674,-0.00344846,-0.00188957,-0.00089754,0.00023620,0.00099202,0.00099202,0.00009448,-0.00042515,-0.00179509,-0.00264539,-0.00231472,-0.00255091,-0.00108650,-0.00108650,0.00037791,-0.00009448,0.00094478,0.00051963,0.00122822,0.00099202,0.00174785,0.00136993,0.00203128,0.00240920,0.00321226,0.00363741,0.00420428,0.00311778,0.00297607,0.00066135,-0.00051963,-0.00222024,-0.00269263,-0.00292883,-0.00226748,-0.00132270,-0.00056687,-0.00028343,-0.00089754,-0.00264539,-0.00382637,-0.00609385,-0.00661348,-0.00741654,-0.00666072,-0.00571594,-0.00396809,-0.00222024,-0.00066135,0.00141717,0.00174785,0.00316502,0.00255091,0.00174785,0.00113374,-0.00094478,-0.00165337,-0.00297607,-0.00354294,-0.00425152,-0.00444048,-0.00562146,-0.00552698,-0.00604661,-0.00581041,-0.00566870,-0.00500735,-0.00486563,-0.00396809,-0.00340122,-0.00292883,-0.00085030,0.00000000,0.00269263,0.00410980,0.00618833,0.00732207,0.00883372,0.00888096,0.01006194,0.00902267,0.00963678,0.00831409,0.00803065,0.00703863,0.00647176,0.00590489,0.00566870,0.00533802,0.00529078,0.00496011,0.00481839,0.00458220,0.00458220,0.00462944,0.00410980,0.00368465,0.00269263,0.00226748,0.00179509,0.00212576,0.00245644,0.00316502,0.00415704,0.00387361,0.00496011,0.00410980,0.00472391,0.00444048,0.00467667,0.00462944,0.00481839,0.00448772,0.00401533,0.00316502,0.00170061,0.00122822,-0.00028343,0.00033067,-0.00023620,0.00089754,0.00155889,0.00240920,0.00273987,0.00269263,0.00155889,0.00028343,-0.00085030,-0.00222024,-0.00212576,-0.00170061,-0.00136993,-0.00023620,-0.00028343,-0.00009448,-0.00085030,-0.00132270,-0.00236196,-0.00283435,-0.00288159,-0.00325950,-0.00255091,-0.00203128,-0.00155889,0.00004724,0.00056687,0.00259815,0.00330674,0.00472391,0.00514907,0.00595213,0.00595213,0.00694415,0.00675520,0.00803065,0.00803065,0.00925887,0.00982574,0.01058157,0.01171531,0.01180978,0.01351039,0.01284904,0.01369935,0.01176254,0.01034537,0.00741654,0.00491287,0.00278711,0.00179509,0.00188957,0.00368465,0.00505459,0.00713311,0.00788894,0.00741654,0.00614109,0.00368465,0.00127546,-0.00047239,-0.00146441,-0.00122822,-0.00094478,-0.00023620,-0.00018896,-0.00108650,-0.00085030,-0.00193680,-0.00094478,-0.00042515,0.00094478,0.00217300,0.00307054,0.00377913,0.00462944,0.00543250,0.00666072,0.00708587,0.00779446,0.00694415,0.00604661,0.00368465,0.00184233,-0.00051963,-0.00188957,-0.00255091,-0.00255091,-0.00103926,0.00028343,0.00278711,0.00425152,0.00647176,0.00675520,0.00736931,0.00585765,0.00467667,0.00311778,0.00155889,0.00141717,0.00103926,0.00207852,0.00250367,0.00330674,0.00335398,0.00344846,0.00377913,0.00500735,0.00680244,0.00977850,0.01209322,0.01473861,0.01469137,0.01464413,0.01129015,0.00864476,0.00429876,0.00122822,-0.00122822,-0.00212576,-0.00231472,-0.00118098,-0.00004724,0.00099202,0.00165337,0.00127546,0.00080307,-0.00042515,-0.00151165,-0.00207852,-0.00297607,-0.00226748,-0.00269263,-0.00250367,-0.00250367,-0.00321226,-0.00311778,-0.00410980,-0.00434600,-0.00477115,-0.00529078,-0.00491287,-0.00533802,-0.00491287,-0.00425152,-0.00392085,-0.00212576,-0.00141717,0.00004724,0.00136993,0.00217300,0.00278711,0.00316502,0.00203128,0.00165337,-0.00066135,-0.00193680,-0.00429876,-0.00566870,-0.00675520,-0.00670796,-0.00595213,-0.00377913,-0.00170061,0.00146441,0.00368465,0.00576317,0.00713311,0.00736931,0.00727483,0.00666072,0.00647176,0.00633004,0.00666072,0.00666072,0.00585765,0.00481839,0.00245644,0.00004724,-0.00250367,-0.00500735,-0.00699139,-0.00826685,-0.00906991,-0.00958954,-0.00925887,-0.00864476,-0.00769998,-0.00604661,-0.00467667,-0.00316502,-0.00151165,-0.00051963,0.00042515,0.00061411,0.00051963,0.00000000,-0.00009448,-0.00023620,0.00089754,0.00184233,0.00368465,0.00481839,0.00651900,0.00684967,0.00817237,0.00803065,0.00869200,0.00836133,0.00817237,0.00788894,0.00732207,0.00751102,0.00755826,0.00807789,0.00892820,0.00892820,0.00992022,0.00940059,0.00982574,0.00949507,0.00869200,0.00812513,0.00628280,0.00519630,0.00316502,0.00250367,0.00207852,0.00212576,0.00321226,0.00325950,0.00377913,0.00292883,0.00212576,0.00061411,-0.00061411,-0.00151165,-0.00193680,-0.00160613,-0.00132270,-0.00080307,-0.00042515,-0.00014172,0.00000000,-0.00018896,-0.00033067,-0.00094478,-0.00094478,-0.00094478,-0.00085030,0.00009448,-0.00014172,0.00066135,-0.00009448,0.00066135,0.00028343,0.00141717,0.00188957,0.00240920,0.00292883,0.00203128,0.00188957,0.00066135,0.00051963,0.00061411,0.00122822,0.00321226,0.00439324,0.00637728,0.00732207,0.00732207,0.00746378,0.00604661,0.00533802,0.00410980,0.00368465,0.00321226,0.00363741,0.00439324,0.00538526,0.00694415,0.00755826,0.00831409,0.00760550,0.00670796,0.00500735,0.00349570,0.00226748,0.00207852,0.00188957,0.00354294,0.00387361,0.00585765,0.00633004,0.00741654,0.00774722,0.00769998,0.00727483,0.00633004,0.00448772,0.00325950,0.00103926,0.00004724,-0.00174785,-0.00231472,-0.00401533,-0.00425152,-0.00533802,-0.00533802,-0.00538526,-0.00415704,-0.00349570,-0.00080307,0.00028343,0.00240920,0.00278711,0.00226748,0.00051963,-0.00311778,-0.00547974,-0.00831409,-0.00803065,-0.00590489,-0.00122822,0.00481839,0.01081776,0.01539996,0.01743124,0.01625026,0.01332144,0.00755826,0.00283435,-0.00321226,-0.00680244,-0.01067604,-0.01162083,-0.01251837,-0.01166807,-0.01062881,-0.00859752,-0.00722759,-0.00486563,-0.00354294,-0.00141717,0.00000000,0.00170061,0.00245644,0.00368465,0.00344846,0.00330674,0.00245644,0.00103926,0.00018896,-0.00094478,-0.00070859,-0.00023620,0.00075583,0.00245644,0.00340122,0.00453496,0.00486563,0.00448772,0.00340122,0.00226748,0.00018896,-0.00103926,-0.00226748,-0.00278711,-0.00269263,-0.00207852,-0.00132270,-0.00023620,0.00009448,0.00085030,0.00070859,0.00113374,0.00113374,0.00155889,0.00155889,0.00151165,0.00051963,-0.00075583,-0.00269263,-0.00392085,-0.00491287,-0.00444048,-0.00349570,-0.00127546,0.00051963,0.00259815,0.00292883,0.00359017,0.00141717,0.00108650,-0.00132270,-0.00236196,-0.00283435,-0.00377913,-0.00297607,-0.00335398,-0.00264539,-0.00283435,-0.00269263,-0.00288159,-0.00321226,-0.00259815,-0.00278711,-0.00141717,-0.00122822,-0.00061411,-0.00051963,-0.00070859,-0.00070859,-0.00085030,-0.00056687,-0.00103926,-0.00118098,-0.00179509,-0.00283435,-0.00302330,-0.00401533,-0.00401533,-0.00392085,-0.00349570,-0.00340122,-0.00231472,-0.00269263,-0.00236196,-0.00250367,-0.00344846,-0.00250367,-0.00340122,-0.00217300,-0.00273987,-0.00217300,-0.00269263,-0.00297607,-0.00340122,-0.00396809,-0.00425152,-0.00462944,-0.00514907,-0.00557422,-0.00590489,-0.00628280,-0.00533802,-0.00529078,-0.00302330,-0.00222024,0.00023620,0.00108650,0.00255091,0.00217300,0.00231472,0.00023620,-0.00094478,-0.00382637,-0.00533802,-0.00703863,-0.00722759,-0.00609385,-0.00396809,-0.00141717,0.00070859,0.00231472,0.00179509,0.00127546,-0.00037791,-0.00141717,-0.00132270,-0.00108650,0.00023620,0.00094478,0.00103926,0.00127546,0.00009448,0.00061411,-0.00023620,0.00108650,0.00089754,0.00217300,0.00203128,0.00188957,0.00089754,-0.00056687,-0.00255091,-0.00401533,-0.00547974,-0.00566870,-0.00538526,-0.00387361,-0.00264539,-0.00051963,0.00108650,0.00231472,0.00307054,0.00316502,0.00188957,0.00146441,-0.00075583,-0.00127546,-0.00259815,-0.00278711,-0.00302330,-0.00269263,-0.00222024,-0.00122822,-0.00047239,0.00070859,0.00174785,0.00184233,0.00207852,0.00061411,0.00000000,-0.00231472,-0.00307054,-0.00481839,-0.00477115,-0.00496011,-0.00410980,-0.00292883,-0.00174785,-0.00028343,0.00056687,0.00122822,0.00132270,0.00122822,0.00099202,0.00141717,0.00099202,0.00245644,0.00193680,0.00387361,0.00387361,0.00562146,0.00566870,0.00642452,0.00618833,0.00581041,0.00529078,0.00472391,0.00448772,0.00406257,0.00410980,0.00321226,0.00297607,0.00212576,0.00240920,0.00184233,0.00321226,0.00325950,0.00481839,0.00543250,0.00647176,0.00755826,0.00812513,0.00883372,0.00850304,0.00727483,0.00571594,0.00330674,0.00094478,0.00014172,-0.00080307,0.00061411,0.00151165,0.00307054,0.00325950,0.00311778,0.00188957,0.00042515,-0.00094478,-0.00188957,-0.00245644,-0.00217300,-0.00231472,-0.00240920,-0.00297607,-0.00344846,-0.00396809,-0.00401533,-0.00354294,-0.00325950,-0.00250367,-0.00273987,-0.00302330,-0.00359017,-0.00439324,-0.00439324,-0.00415704,-0.00311778,-0.00264539,-0.00170061,-0.00203128,-0.00179509,-0.00184233,-0.00094478,-0.00028343,0.00118098,0.00075583,0.00089754,-0.00075583,-0.00113374,-0.00222024,-0.00151165,-0.00118098,0.00037791,0.00132270,0.00231472,0.00359017,0.00382637,0.00514907,0.00529078,0.00524354,0.00581041,0.00420428,0.00444048,0.00255091,0.00236196,0.00146441,0.00113374,0.00099202,0.00000000,-0.00042515,-0.00217300,-0.00283435,-0.00387361,-0.00302330,-0.00203128,0.00009448,0.00193680,0.00382637,0.00481839,0.00505459,0.00453496,0.00340122,0.00222024,0.00108650,0.00042515,-0.00033067,-0.00042515,-0.00061411,-0.00094478,-0.00056687,-0.00113374,-0.00080307,-0.00056687,-0.00066135,0.00066135,0.00085030,0.00212576,0.00250367,0.00278711,0.00250367,0.00226748,0.00141717,0.00151165,0.00122822,0.00179509,0.00226748,0.00307054,0.00392085,0.00477115,0.00529078,0.00566870,0.00552698,0.00562146,0.00477115,0.00448772,0.00335398,0.00283435,0.00165337,0.00080307,-0.00009448,-0.00085030,-0.00080307,-0.00033067,0.00080307,0.00222024,0.00396809,0.00448772,0.00505459,0.00396809,0.00250367,0.00170061,-0.00004724,0.00014172,0.00014172,0.00051963,0.00179509,0.00198404,0.00292883,0.00302330,0.00340122,0.00349570,0.00373189,0.00373189,0.00340122,0.00288159,0.00132270,0.00000000,-0.00184233,-0.00316502,-0.00377913,-0.00387361,-0.00359017,-0.00226748,-0.00146441,-0.00023620,0.00042515,-0.00004724,-0.00014172,-0.00146441,-0.00174785,-0.00207852,-0.00174785,-0.00075583,-0.00037791,0.00018896,-0.00033067,-0.00127546,-0.00236196,-0.00406257,-0.00415704,-0.00373189,-0.00170061,0.00141717,0.00377913,0.00628280,0.00656624,0.00595213,0.00311778,-0.00085030,-0.00538526,-0.00987298,-0.01218770,-0.01261285,-0.00977850,-0.00514907,0.00066135,0.00585765,0.00916439,0.01095948,0.00954231,0.00769998,0.00401533,0.00094478,-0.00222024,-0.00425152,-0.00500735,-0.00491287,-0.00439324,-0.00325950,-0.00330674,-0.00255091,-0.00292883,-0.00259815,-0.00278711,-0.00236196,-0.00188957,-0.00099202,-0.00009448,0.00118098,0.00146441,0.00188957,0.00103926,-0.00004724,-0.00075583,-0.00226748,-0.00179509,-0.00203128,-0.00070859,0.00061411,0.00179509,0.00288159,0.00382637,0.00321226,0.00392085,0.00231472,0.00259815,0.00222024,0.00240920,0.00363741,0.00444048,0.00609385,0.00765274,0.00859752,0.00911715,0.00911715,0.00817237,0.00694415,0.00557422,0.00325950,0.00250367,0.00127546,0.00170061,0.00259815,0.00382637,0.00562146,0.00675520,0.00718035,0.00713311,0.00595213,0.00505459,0.00382637,0.00368465,0.00340122,0.00406257,0.00448772,0.00491287,0.00467667,0.00481839,0.00425152,0.00481839,0.00444048,0.00429876,0.00354294,0.00160613,0.00014172,-0.00174785,-0.00316502,-0.00325950,-0.00363741,-0.00283435,-0.00278711,-0.00264539,-0.00344846,-0.00444048,-0.00529078,-0.00647176,-0.00614109,-0.00576317,-0.00467667,-0.00373189,-0.00278711,-0.00259815,-0.00222024,-0.00236196,-0.00184233,-0.00231472,-0.00160613,-0.00226748,-0.00184233,-0.00094478,-0.00042515,0.00188957,0.00273987,0.00392085,0.00382637,0.00307054,0.00174785,0.00047239,-0.00018896,-0.00056687,-0.00037791,0.00042515,0.00061411,0.00151165,0.00170061,0.00212576,0.00217300,0.00217300,0.00193680,0.00165337,0.00193680,0.00174785,0.00292883,0.00283435,0.00392085,0.00292883,0.00269263,0.00122822,-0.00061411,-0.00141717,-0.00344846,-0.00307054,-0.00373189,-0.00264539,-0.00217300,-0.00047239,0.00000000,0.00170061,0.00188957,0.00217300,0.00226748,0.00146441,0.00118098,0.00061411,0.00061411,0.00033067,0.00094478,0.00056687,0.00085030,0.00075583,0.00066135,0.00118098,0.00141717,0.00236196,0.00207852,0.00222024,0.00108650,0.00023620,-0.00080307,-0.00151165,-0.00132270,-0.00118098,-0.00037791,0.00000000,0.00004724,-0.00014172,-0.00174785,-0.00226748,-0.00425152,-0.00444048,-0.00590489,-0.00552698,-0.00633004,-0.00538526,-0.00547974,-0.00415704,-0.00387361,-0.00245644,-0.00250367,-0.00179509,-0.00217300,-0.00245644,-0.00302330,-0.00359017,-0.00368465,-0.00368465,-0.00373189,-0.00307054,-0.00321226,-0.00236196,-0.00245644,-0.00184233,-0.00203128,-0.00174785,-0.00198404,-0.00203128,-0.00207852,-0.00203128,-0.00217300,-0.00245644,-0.00335398,-0.00382637,-0.00472391,-0.00462944,-0.00491287,-0.00330674,-0.00307054,-0.00070859,-0.00047239,0.00056687,0.00018896,-0.00014172,-0.00160613,-0.00222024,-0.00325950,-0.00307054,-0.00255091,-0.00160613,-0.00066135,-0.00023620,-0.00047239,-0.00193680,-0.00292883,-0.00444048,-0.00524354,-0.00557422,-0.00595213,-0.00514907,-0.00566870,-0.00472391,-0.00562146,-0.00472391,-0.00524354,-0.00410980,-0.00406257,-0.00278711,-0.00278711,-0.00255091,-0.00273987,-0.00335398,-0.00335398,-0.00396809,-0.00354294,-0.00415704,-0.00325950,-0.00420428,-0.00425152,-0.00533802,-0.00670796,-0.00713311,-0.00826685,-0.00765274,-0.00769998,-0.00751102,-0.00732207,-0.00793617,-0.00850304,-0.00869200,-0.00911715,-0.00831409,-0.00727483,-0.00595213,-0.00420428,-0.00311778,-0.00212576,-0.00174785,-0.00155889,-0.00141717,-0.00141717,-0.00103926,-0.00132270,-0.00132270,-0.00174785,-0.00250367,-0.00283435,-0.00363741,-0.00363741,-0.00392085,-0.00415704,-0.00434600,-0.00491287,-0.00524354,-0.00552698,-0.00547974,-0.00467667,-0.00368465,-0.00212576,-0.00075583,0.00070859,0.00051963,0.00094478,-0.00047239,-0.00113374,-0.00217300,-0.00245644,-0.00292883,-0.00255091,-0.00255091,-0.00226748,-0.00174785,-0.00136993,-0.00047239,0.00113374,0.00203128,0.00354294,0.00349570,0.00245644,0.00094478,-0.00141717,-0.00354294,-0.00467667,-0.00543250,-0.00557422,-0.00434600,-0.00444048,-0.00240920,-0.00198404,-0.00056687,0.00037791,0.00127546,0.00146441,0.00250367,0.00193680,0.00250367,0.00136993,0.00118098,-0.00051963,-0.00085030,-0.00240920,-0.00259815,-0.00297607,-0.00264539,-0.00222024,-0.00203128,-0.00198404,-0.00240920,-0.00311778,-0.00415704,-0.00491287,-0.00581041,-0.00614109,-0.00670796,-0.00666072,-0.00633004,-0.00529078,-0.00377913,-0.00179509,0.00009448,0.00179509,0.00325950,0.00425152,0.00439324,0.00481839,0.00349570,0.00335398,0.00174785,0.00103926,0.00004724,-0.00056687,-0.00113374,-0.00174785,-0.00222024,-0.00406257,-0.00453496,-0.00708587,-0.00746378,-0.00911715,-0.00888096,-0.00873924,-0.00760550,-0.00651900,-0.00500735,-0.00420428,-0.00321226,-0.00269263,-0.00250367,-0.00132270,-0.00132270,0.00061411,0.00113374,0.00269263,0.00273987,0.00240920,0.00127546,-0.00023620,-0.00184233,-0.00278711,-0.00368465,-0.00349570,-0.00311778,-0.00207852,-0.00103926,0.00070859,0.00122822,0.00259815,0.00226748,0.00269263,0.00198404,0.00207852,0.00165337,0.00170061,0.00193680,0.00155889,0.00203128,0.00132270,0.00146441,0.00108650,0.00113374,0.00118098,0.00099202,0.00018896,-0.00023620,-0.00222024,-0.00297607,-0.00429876,-0.00434600,-0.00363741,-0.00240920,-0.00056687,0.00113374,0.00273987,0.00344846,0.00392085,0.00325950,0.00255091,0.00118098,-0.00004724,-0.00113374,-0.00236196,-0.00264539,-0.00288159,-0.00222024,-0.00118098,-0.00028343,0.00061411,0.00108650,0.00070859,0.00033067,-0.00061411,-0.00160613,-0.00269263,-0.00349570,-0.00472391,-0.00462944,-0.00529078,-0.00477115,-0.00453496,-0.00406257,-0.00377913,-0.00354294,-0.00264539,-0.00250367,-0.00099202,-0.00080307,-0.00004724,-0.00009448,-0.00042515,-0.00108650,-0.00170061,-0.00240920,-0.00245644,-0.00250367,-0.00127546,-0.00042515,0.00141717,0.00245644,0.00373189,0.00349570,0.00377913,0.00273987,0.00269263,0.00217300,0.00269263,0.00264539,0.00316502,0.00330674,0.00264539,0.00297607,0.00184233,0.00179509,0.00047239,0.00018896,-0.00118098,-0.00061411,-0.00056687,0.00099202,0.00217300,0.00429876,0.00500735,0.00614109,0.00618833,0.00595213,0.00562146,0.00543250,0.00467667,0.00472391,0.00415704,0.00363741,0.00325950,0.00207852,0.00198404,0.00089754,0.00037791,0.00009448,-0.00075583,-0.00056687,-0.00080307,-0.00122822,-0.00056687,-0.00118098,-0.00014172,-0.00075583,0.00047239,0.00000000,0.00108650,0.00132270,0.00226748,0.00307054,0.00396809,0.00486563,0.00538526,0.00576317,0.00562146,0.00481839,0.00401533,0.00222024,0.00075583,-0.00113374,-0.00283435,-0.00392085,-0.00491287,-0.00510183,-0.00510183,-0.00439324,-0.00396809,-0.00297607,-0.00292883,-0.00292883,-0.00335398,-0.00363741,-0.00382637,-0.00307054,-0.00273987,-0.00184233,-0.00094478,-0.00033067,0.00028343,0.00141717,0.00141717,0.00203128,0.00207852,0.00141717,0.00160613,0.00075583,0.00118098,0.00103926,0.00094478,0.00103926,0.00066135,0.00023620,0.00061411,-0.00037791,-0.00009448,-0.00075583,-0.00113374,-0.00160613,-0.00146441,-0.00141717,-0.00042515,0.00047239,0.00184233,0.00307054,0.00401533,0.00429876,0.00448772,0.00340122,0.00321226,0.00207852,0.00222024,0.00203128,0.00316502,0.00373189,0.00514907,0.00529078,0.00566870,0.00467667,0.00288159,0.00108650,-0.00122822,-0.00231472,-0.00302330,-0.00273987,-0.00250367,-0.00193680,-0.00335398,-0.00491287,-0.00788894,-0.00921163,-0.00963678,-0.00675520,-0.00283435,0.00278711,0.00703863,0.00935335,0.00958954,0.00670796,0.00401533,-0.00047239,-0.00325950,-0.00633004,-0.00788894,-0.00921163,-0.00987298,-0.00977850,-0.00958954,-0.00873924,-0.00784170,-0.00718035,-0.00623557,-0.00543250,-0.00477115,-0.00373189,-0.00311778,-0.00226748,-0.00226748,-0.00193680,-0.00330674,-0.00359017,-0.00486563,-0.00472391,-0.00396809,-0.00245644,0.00047239,0.00288159,0.00609385,0.00751102,0.00845581,0.00732207,0.00524354,0.00203128,-0.00132270,-0.00392085,-0.00595213,-0.00618833,-0.00552698,-0.00392085,-0.00188957,0.00056687,0.00174785,0.00302330,0.00273987,0.00184233,0.00094478,-0.00099202,-0.00160613,-0.00335398,-0.00302330,-0.00377913,-0.00255091,-0.00155889,-0.00009448,0.00165337,0.00250367,0.00302330,0.00212576,0.00089754,-0.00136993,-0.00382637,-0.00595213,-0.00803065,-0.00873924,-0.00911715,-0.00826685,-0.00722759,-0.00585765,-0.00477115,-0.00434600,-0.00425152,-0.00514907,-0.00566870,-0.00680244,-0.00736931,-0.00656624,-0.00647176,-0.00401533,-0.00316502,-0.00127546,-0.00080307,-0.00108650,-0.00188957,-0.00335398,-0.00420428,-0.00524354,-0.00510183,-0.00514907,-0.00481839,-0.00491287,-0.00552698,-0.00609385,-0.00694415,-0.00656624,-0.00670796,-0.00571594,-0.00519630,-0.00500735,-0.00496011,-0.00538526,-0.00566870,-0.00538526,-0.00448772,-0.00368465,-0.00188957,-0.00122822,0.00028343,0.00033067,0.00056687,0.00056687,0.00018896,0.00066135,0.00004724,0.00085030,0.00000000,0.00000000,-0.00066135,-0.00089754,-0.00080307,0.00004724,0.00094478,0.00240920,0.00278711,0.00340122,0.00273987,0.00240920,0.00122822,0.00103926,-0.00042515,-0.00014172,-0.00155889,-0.00118098,-0.00207852,-0.00179509,-0.00236196,-0.00193680,-0.00222024,-0.00231472,-0.00203128,-0.00264539,-0.00273987,-0.00363741,-0.00425152,-0.00533802,-0.00510183,-0.00547974,-0.00420428,-0.00330674,-0.00160613,-0.00047239,0.00099202,0.00113374,0.00155889,0.00146441,0.00165337,0.00207852,0.00307054,0.00392085,0.00491287,0.00538526,0.00547974,0.00547974,0.00514907,0.00486563,0.00510183,0.00406257,0.00444048,0.00302330,0.00240920,0.00188957,0.00118098,0.00136993,0.00141717,0.00170061,0.00174785,0.00217300,0.00188957,0.00217300,0.00222024,0.00250367,0.00302330,0.00387361,0.00448772,0.00571594,0.00628280,0.00703863,0.00675520,0.00651900,0.00491287,0.00396809,0.00174785,0.00075583,-0.00056687,-0.00170061,-0.00193680,-0.00264539,-0.00297607,-0.00269263,-0.00359017,-0.00330674,-0.00377913,-0.00363741,-0.00349570,-0.00273987,-0.00160613,-0.00051963,0.00132270,0.00170061,0.00307054,0.00245644,0.00297607,0.00155889,0.00193680,0.00051963,0.00136993,0.00061411,0.00170061,0.00198404,0.00297607,0.00377913,0.00406257,0.00439324,0.00344846,0.00288159,0.00146441,0.00132270,0.00085030,0.00160613,0.00236196,0.00359017,0.00472391,0.00566870,0.00651900,0.00656624,0.00694415,0.00618833,0.00614109,0.00557422,0.00500735,0.00453496,0.00420428,0.00321226,0.00311778,0.00170061,0.00085030,-0.00051963,-0.00165337,-0.00297607,-0.00297607,-0.00382637,-0.00297607,-0.00297607,-0.00264539,-0.00283435,-0.00273987,-0.00363741,-0.00335398,-0.00439324,-0.00496011,-0.00585765,-0.00713311,-0.00821961,-0.00925887,-0.01039261,-0.01081776,-0.01124291,-0.01133739,-0.01067604,-0.00973126,-0.00850304,-0.00661348,-0.00590489,-0.00510183,-0.00496011,-0.00524354,-0.00481839,-0.00496011,-0.00392085,-0.00325950,-0.00231472,-0.00160613,-0.00155889,-0.00160613,-0.00212576,-0.00273987,-0.00344846,-0.00396809,-0.00439324,-0.00444048,-0.00387361,-0.00325950,-0.00184233,-0.00151165,-0.00018896,-0.00089754,-0.00070859,-0.00198404,-0.00250367,-0.00335398,-0.00354294,-0.00269263,-0.00231472,-0.00056687,-0.00056687,0.00042515,-0.00009448,0.00037791,-0.00066135,-0.00009448,-0.00108650,-0.00066135,-0.00141717,-0.00160613,-0.00160613,-0.00236196,-0.00222024,-0.00335398,-0.00420428,-0.00576317,-0.00694415,-0.00826685,-0.00855028,-0.00864476,-0.00765274,-0.00623557,-0.00543250,-0.00387361,-0.00396809,-0.00373189,-0.00458220,-0.00505459,-0.00604661,-0.00670796,-0.00769998,-0.00774722,-0.00850304,-0.00699139,-0.00684967,-0.00406257,-0.00264539,0.00033067,0.00188957,0.00344846,0.00477115,0.00458220,0.00529078,0.00491287,0.00510183,0.00543250,0.00538526,0.00547974,0.00477115,0.00448772,0.00344846,0.00325950,0.00269263,0.00292883,0.00245644,0.00283435,0.00245644,0.00222024,0.00165337,0.00103926,-0.00014172,-0.00042515,-0.00155889,-0.00075583,-0.00108650,0.00042515,0.00056687,0.00136993,0.00132270,0.00127546,0.00118098,0.00113374,0.00146441,0.00193680,0.00240920,0.00302330,0.00335398,0.00340122,0.00335398,0.00278711,0.00222024,0.00089754,0.00028343,-0.00132270,-0.00094478,-0.00094478,0.00061411,0.00273987,0.00448772,0.00727483,0.00821961,0.00935335,0.00916439,0.00807789,0.00736931,0.00562146,0.00481839,0.00368465,0.00359017,0.00316502,0.00401533,0.00373189,0.00453496,0.00396809,0.00354294,0.00250367,0.00061411,-0.00089754,-0.00240920,-0.00354294,-0.00297607,-0.00269263,-0.00056687,0.00132270,0.00340122,0.00496011,0.00595213,0.00562146,0.00477115,0.00292883,0.00118098,0.00014172,-0.00103926,-0.00047239,0.00000000,0.00127546,0.00269263,0.00382637,0.00448772,0.00486563,0.00429876,0.00401533,0.00316502,0.00255091,0.00193680,0.00113374,0.00066135,-0.00085030,-0.00113374,-0.00269263,-0.00250367,-0.00278711,-0.00231472,-0.00099202,-0.00094478,0.00051963,0.00018896,0.00033067,0.00033067,-0.00037791,0.00009448,-0.00014172,0.00080307,0.00099202,0.00184233,0.00179509,0.00170061,0.00089754,0.00028343,-0.00094478,-0.00127546,-0.00184233,-0.00226748,-0.00264539,-0.00302330,-0.00344846,-0.00368465,-0.00349570,-0.00359017,-0.00278711,-0.00250367,-0.00222024,-0.00136993,-0.00118098,-0.00028343,0.00023620,0.00014172,0.00009448,-0.00056687,-0.00193680,-0.00259815,-0.00415704,-0.00458220,-0.00505459,-0.00496011,-0.00415704,-0.00321226,-0.00170061,-0.00042515,0.00094478,0.00141717,0.00203128,0.00094478,0.00085030,-0.00051963,-0.00080307,-0.00103926,-0.00070859,-0.00066135,0.00051963,0.00056687,0.00203128,0.00250367,0.00340122,0.00311778,0.00236196,0.00103926,-0.00099202,-0.00264539,-0.00354294,-0.00514907,-0.00420428,-0.00505459,-0.00359017,-0.00349570,-0.00184233,-0.00136993,-0.00014172,-0.00018896,-0.00033067,-0.00108650,-0.00226748,-0.00250367,-0.00259815,-0.00127546,0.00085030,0.00311778,0.00562146,0.00718035,0.00812513,0.00769998,0.00647176,0.00429876,0.00165337,-0.00028343,-0.00259815,-0.00321226,-0.00354294,-0.00321226,-0.00207852,-0.00132270,-0.00009448,0.00080307,0.00179509,0.00226748,0.00222024,0.00174785,0.00070859,-0.00051963,-0.00160613,-0.00245644,-0.00278711,-0.00264539,-0.00184233,-0.00155889,0.00014172,0.00061411,0.00264539,0.00420428,0.00595213,0.00784170,0.00845581,0.00916439,0.00732207,0.00618833,0.00297607,0.00118098,-0.00085030,-0.00226748,-0.00297607,-0.00420428,-0.00425152,-0.00514907,-0.00510183,-0.00486563,-0.00434600,-0.00349570,-0.00231472,-0.00132270,-0.00023620,0.00075583,0.00113374,0.00136993,0.00099202,0.00014172,0.00004724,-0.00085030,-0.00014172,-0.00047239,0.00033067,0.00037791,-0.00018896,-0.00089754,-0.00307054,-0.00481839,-0.00708587,-0.00821961,-0.00944783,-0.00869200,-0.00869200,-0.00670796,-0.00529078,-0.00325950,-0.00122822,0.00042515,0.00198404,0.00325950,0.00387361,0.00538526,0.00486563,0.00651900,0.00547974,0.00623557,0.00533802,0.00491287,0.00387361,0.00269263,0.00179509,0.00042515,-0.00009448,-0.00113374,-0.00108650,-0.00170061,-0.00122822,-0.00160613,-0.00103926,-0.00113374,-0.00094478,-0.00099202,-0.00122822,-0.00132270,-0.00108650,-0.00122822,-0.00004724,-0.00042515,0.00075583,0.00061411,0.00132270,0.00165337,0.00165337,0.00141717,0.00042515,-0.00056687,-0.00184233,-0.00259815,-0.00302330,-0.00226748,-0.00132270,0.00018896,0.00184233,0.00245644,0.00354294,0.00325950,0.00307054,0.00307054,0.00217300,0.00302330,0.00245644,0.00325950,0.00307054,0.00335398,0.00278711,0.00330674,0.00330674,0.00448772,0.00562146,0.00675520,0.00779446,0.00793617,0.00718035,0.00637728,0.00401533,0.00255091,0.00033067,-0.00118098,-0.00231472,-0.00245644,-0.00184233,-0.00089754,0.00103926,0.00174785,0.00321226,0.00330674,0.00359017,0.00278711,0.00273987,0.00155889,0.00113374,0.00033067,0.00014172,-0.00023620,0.00023620,0.00056687,0.00184233,0.00283435,0.00434600,0.00477115,0.00604661,0.00557422,0.00637728,0.00585765,0.00642452,0.00689691,0.00765274,0.00878648,0.00892820,0.00963678,0.00878648,0.00906991,0.00774722,0.00755826,0.00609385,0.00552698,0.00420428,0.00354294,0.00297607,0.00264539,0.00231472,0.00259815,0.00217300,0.00170061,0.00127546,-0.00018896,-0.00075583,-0.00118098,-0.00203128,-0.00160613,-0.00222024,-0.00231472,-0.00278711,-0.00330674,-0.00387361,-0.00363741,-0.00344846,-0.00236196,-0.00080307,0.00018896,0.00174785,0.00207852,0.00255091,0.00212576,0.00226748,0.00146441,0.00217300,0.00160613,0.00302330,0.00288159,0.00415704,0.00406257,0.00429876,0.00392085,0.00321226,0.00240920,0.00193680,0.00070859,0.00122822,0.00037791,0.00155889,0.00226748,0.00434600,0.00552698,0.00755826,0.00798341,0.00850304,0.00864476,0.00788894,0.00803065,0.00722759,0.00661348,0.00543250,0.00406257,0.00273987,0.00198404,0.00136993,0.00212576,0.00222024,0.00344846,0.00349570,0.00340122,0.00288159,0.00236196,0.00136993,0.00132270,0.00118098,0.00089754,0.00174785,0.00080307,0.00122822,0.00080307,0.00042515,0.00151165,0.00151165,0.00368465,0.00462944,0.00637728,0.00765274,0.00836133,0.00878648,0.00840857,0.00732207,0.00651900,0.00477115,0.00453496,0.00335398,0.00368465,0.00406257,0.00420428,0.00529078,0.00491287,0.00547974,0.00462944,0.00453496,0.00377913,0.00354294,0.00325950,0.00335398,0.00340122,0.00316502,0.00330674,0.00259815,0.00222024,0.00250367,0.00188957,0.00316502,0.00368465,0.00510183,0.00609385,0.00694415,0.00633004,0.00581041,0.00368465,0.00217300,0.00033067,-0.00075583,-0.00103926,-0.00070859,-0.00009448,0.00132270,0.00255091,0.00429876,0.00562146,0.00661348,0.00689691,0.00647176,0.00628280,0.00543250,0.00552698,0.00514907,0.00557422,0.00514907,0.00519630,0.00396809,0.00269263,0.00174785,-0.00009448,-0.00075583,-0.00146441,-0.00174785,-0.00080307,-0.00028343,0.00094478,0.00226748,0.00255091,0.00373189,0.00269263,0.00311778,0.00132270,0.00085030,-0.00118098,-0.00122822,-0.00245644,-0.00089754,-0.00023620,0.00155889,0.00321226,0.00373189,0.00472391,0.00420428,0.00425152,0.00325950,0.00278711,0.00174785,0.00075583,0.00033067,-0.00066135,0.00018896,0.00000000,0.00146441,0.00094478,0.00174785,0.00066135,0.00075583,0.00018896,0.00094478,0.00151165,0.00325950,0.00396809,0.00491287,0.00529078,0.00533802,0.00514907,0.00529078,0.00500735,0.00420428,0.00448772,0.00269263,0.00273987,0.00226748,0.00203128,0.00359017,0.00396809,0.00543250,0.00576317,0.00618833,0.00533802,0.00519630,0.00387361,0.00392085,0.00368465,0.00368465,0.00396809,0.00359017,0.00316502,0.00212576,0.00080307,-0.00113374,-0.00269263,-0.00434600,-0.00529078,-0.00510183,-0.00415704,-0.00222024,-0.00042515,0.00146441,0.00231472,0.00250367,0.00222024,0.00113374,0.00099202,0.00014172,0.00028343,-0.00033067,-0.00004724,-0.00070859,-0.00080307,-0.00146441,-0.00122822,-0.00118098,-0.00028343,0.00037791,0.00136993,0.00226748,0.00188957,0.00259815,0.00089754,0.00103926,-0.00018896,-0.00066135,-0.00089754,-0.00127546,-0.00094478,-0.00113374,-0.00075583,-0.00094478,-0.00094478,-0.00051963,-0.00023620,0.00056687,0.00170061,0.00250367,0.00344846,0.00363741,0.00359017,0.00330674,0.00307054,0.00297607,0.00283435,0.00264539,0.00278711,0.00245644,0.00259815,0.00240920,0.00179509,0.00179509,0.00018896,-0.00023620,-0.00170061,-0.00255091,-0.00316502,-0.00316502,-0.00307054,-0.00207852,-0.00132270,-0.00066135,0.00033067,0.00018896,0.00075583,0.00122822,0.00212576,0.00340122,0.00481839,0.00552698,0.00614109,0.00590489,0.00524354,0.00406257,0.00278711,0.00033067,-0.00085030,-0.00316502,-0.00406257,-0.00406257,-0.00377913,-0.00160613,-0.00018896,0.00245644,0.00373189,0.00529078,0.00543250,0.00481839,0.00406257,0.00217300,0.00051963,-0.00108650,-0.00236196,-0.00330674,-0.00311778,-0.00307054,-0.00198404,-0.00108650,0.00004724,0.00085030,0.00113374,0.00146441,0.00056687,0.00018896,-0.00018896,-0.00056687,-0.00009448,0.00066135,0.00141717,0.00269263,0.00311778,0.00335398,0.00325950,0.00264539,0.00188957,0.00075583,0.00037791,-0.00066135,0.00009448,0.00028343,0.00170061,0.00311778,0.00392085,0.00467667,0.00467667,0.00377913,0.00340122,0.00255091,0.00226748,0.00269263,0.00297607,0.00406257,0.00415704,0.00524354,0.00439324,0.00505459,0.00330674,0.00330674,0.00174785,0.00170061,0.00132270,0.00188957,0.00250367,0.00359017,0.00373189,0.00458220,0.00396809,0.00415704,0.00382637,0.00344846,0.00368465,0.00273987,0.00250367,0.00113374,-0.00075583,-0.00269263,-0.00533802,-0.00741654,-0.00883372,-0.00992022,-0.00935335,-0.00916439,-0.00751102,-0.00684967,-0.00524354,-0.00477115,-0.00335398,-0.00269263,-0.00103926,0.00009448,0.00151165,0.00283435,0.00382637,0.00458220,0.00510183,0.00467667,0.00477115,0.00349570,0.00292883,0.00170061,0.00066135,0.00023620,0.00000000,0.00028343,0.00113374,0.00141717,0.00160613,0.00160613,0.00042515,-0.00099202,-0.00278711,-0.00448772,-0.00604661,-0.00609385,-0.00637728,-0.00529078,-0.00401533,-0.00231472,-0.00108650,0.00094478,0.00146441,0.00259815,0.00250367,0.00297607,0.00198404,0.00250367,0.00165337,0.00160613,0.00089754,-0.00033067,-0.00108650,-0.00231472,-0.00302330,-0.00321226,-0.00349570,-0.00250367,-0.00193680,-0.00136993,-0.00070859,-0.00113374,-0.00127546,-0.00217300,-0.00283435,-0.00302330,-0.00297607,-0.00212576,-0.00132270,-0.00014172,0.00023620,0.00151165,0.00113374,0.00288159,0.00245644,0.00392085,0.00396809,0.00467667,0.00467667,0.00491287,0.00410980,0.00396809,0.00203128,0.00136993,-0.00061411,-0.00136993,-0.00250367,-0.00335398,-0.00363741,-0.00491287,-0.00514907,-0.00666072,-0.00713311,-0.00765274,-0.00722759,-0.00642452,-0.00491287,-0.00363741,-0.00269263,-0.00222024,-0.00264539,-0.00321226,-0.00396809,-0.00420428,-0.00439324,-0.00359017,-0.00316502,-0.00193680,-0.00075583,-0.00014172,0.00122822,0.00146441,0.00255091,0.00240920,0.00269263,0.00151165,0.00066135,-0.00122822,-0.00269263,-0.00363741,-0.00448772,-0.00387361,-0.00311778,-0.00132270,0.00051963,0.00297607,0.00382637,0.00566870,0.00458220,0.00486563,0.00302330,0.00255091,0.00056687,-0.00009448,-0.00179509,-0.00188957,-0.00292883,-0.00222024,-0.00250367,-0.00155889,-0.00118098,-0.00009448,0.00042515,0.00179509,0.00222024,0.00297607,0.00278711,0.00236196,0.00193680,0.00099202,0.00099202,0.00066135,0.00108650,0.00198404,0.00250367,0.00387361,0.00387361,0.00453496,0.00382637,0.00373189,0.00321226,0.00255091,0.00207852,0.00070859,0.00033067,-0.00122822,-0.00080307,-0.00118098,0.00047239,0.00108650,0.00217300,0.00170061,0.00094478,0.00023620,-0.00122822,-0.00056687,-0.00113374,0.00061411,0.00103926,0.00207852,0.00292883,0.00330674,0.00368465,0.00401533,0.00292883,0.00288159,0.00132270,0.00080307,0.00056687,0.00004724,0.00066135,0.00014172,-0.00004724,-0.00132270,-0.00335398,-0.00505459,-0.00746378,-0.00826685,-0.00888096,-0.00836133,-0.00699139,-0.00557422,-0.00420428,-0.00297607,-0.00311778,-0.00273987,-0.00387361,-0.00401533,-0.00467667,-0.00425152,-0.00359017,-0.00184233,-0.00033067,0.00160613,0.00321226,0.00344846,0.00429876,0.00217300,0.00155889,-0.00146441,-0.00264539,-0.00387361,-0.00392085,-0.00321226,-0.00160613,-0.00070859,0.00033067,0.00056687,0.00000000,-0.00066135,-0.00132270,-0.00188957,-0.00207852,-0.00174785,-0.00222024,-0.00207852,-0.00307054,-0.00406257,-0.00543250,-0.00647176,-0.00751102,-0.00727483,-0.00765274,-0.00590489,-0.00496011,-0.00283435,-0.00108650,0.00023620,0.00122822,0.00127546,0.00047239,-0.00094478,-0.00259815,-0.00472391,-0.00543250,-0.00651900,-0.00566870,-0.00496011,-0.00354294,-0.00222024,-0.00132270,-0.00099202,-0.00094478,-0.00179509,-0.00198404,-0.00316502,-0.00359017,-0.00415704,-0.00514907,-0.00505459,-0.00609385,-0.00543250,-0.00595213,-0.00434600,-0.00420428,-0.00212576,-0.00165337,-0.00108650,-0.00174785,-0.00377913,-0.00633004,-0.00836133,-0.00992022,-0.00935335,-0.00722759,-0.00425152,-0.00023620,0.00255091,0.00519630,0.00557422,0.00562146,0.00373189,0.00151165,-0.00042515,-0.00283435,-0.00434600,-0.00585765,-0.00746378,-0.00864476,-0.00916439,-0.01006194,-0.00925887,-0.00888096,-0.00703863,-0.00533802,-0.00340122,-0.00236196,-0.00089754,-0.00099202,-0.00047239,-0.00089754,-0.00051963,-0.00094478,-0.00028343,-0.00080307,-0.00089754,-0.00080307,-0.00108650,-0.00099202,-0.00080307,-0.00188957,-0.00264539,-0.00434600,-0.00623557,-0.00675520,-0.00727483,-0.00533802,-0.00340122,0.00000000,0.00335398,0.00604661,0.00769998,0.00817237,0.00661348,0.00477115,0.00212576,0.00023620,-0.00099202,-0.00089754,-0.00028343,0.00051963,0.00184233,0.00217300,0.00231472,0.00245644,0.00151165,0.00151165,0.00085030,0.00080307,0.00023620,0.00051963,-0.00018896,-0.00028343,-0.00089754,-0.00203128,-0.00226748,-0.00311778,-0.00297607,-0.00344846,-0.00335398,-0.00387361,-0.00472391,-0.00585765,-0.00722759,-0.00845581,-0.00883372,-0.00963678,-0.00878648,-0.00902267,-0.00774722,-0.00788894,-0.00651900,-0.00571594,-0.00453496,-0.00250367,-0.00188957,0.00028343,0.00028343,0.00103926,0.00051963,0.00000000,-0.00108650,-0.00245644,-0.00344846,-0.00439324,-0.00410980,-0.00420428,-0.00335398,-0.00245644,-0.00212576,-0.00141717,-0.00212576,-0.00236196,-0.00307054,-0.00448772,-0.00538526,-0.00722759,-0.00798341,-0.00878648,-0.00826685,-0.00718035,-0.00533802,-0.00335398,-0.00207852,-0.00136993,-0.00113374,-0.00198404,-0.00193680,-0.00273987,-0.00255091,-0.00259815,-0.00259815,-0.00203128,-0.00198404,-0.00146441,-0.00141717,-0.00193680,-0.00193680,-0.00302330,-0.00292883,-0.00387361,-0.00420428,-0.00529078,-0.00595213,-0.00680244,-0.00718035,-0.00699139,-0.00604661,-0.00496011,-0.00344846,-0.00222024,-0.00136993,-0.00014172,-0.00018896,0.00080307,0.00033067,0.00103926,0.00070859,0.00136993,0.00151165,0.00207852,0.00217300,0.00207852,0.00188957,0.00108650,0.00118098,0.00066135,0.00089754,0.00056687,0.00023620,-0.00018896,-0.00141717,-0.00226748,-0.00382637,-0.00434600,-0.00562146,-0.00533802,-0.00552698,-0.00496011,-0.00396809,-0.00382637,-0.00278711,-0.00217300,-0.00165337,-0.00037791,0.00028343,0.00075583,0.00122822,0.00042515,-0.00047239,-0.00207852,-0.00406257,-0.00533802,-0.00661348,-0.00680244,-0.00680244,-0.00656624,-0.00680244,-0.00684967,-0.00774722,-0.00708587,-0.00633004,-0.00401533,-0.00136993,0.00103926,0.00278711,0.00340122,0.00283435,0.00226748,0.00037791,-0.00004724,-0.00113374,-0.00118098,-0.00056687,-0.00094478,-0.00066135,-0.00188957,-0.00307054,-0.00434600,-0.00481839,-0.00543250,-0.00406257,-0.00377913,-0.00170061,-0.00146441,0.00066135,0.00136993,0.00335398,0.00491287,0.00642452,0.00779446,0.00873924,0.00888096,0.00793617,0.00680244,0.00439324,0.00302330,0.00174785,0.00170061,0.00146441,0.00118098,-0.00009448,-0.00198404,-0.00377913,-0.00396809,-0.00396809,-0.00118098,0.00099202,0.00335398,0.00510183,0.00557422,0.00571594,0.00524354,0.00401533,0.00222024,0.00061411,-0.00207852,-0.00283435,-0.00325950,-0.00222024,0.00047239,0.00259815,0.00547974,0.00699139,0.00708587,0.00684967,0.00510183,0.00410980,0.00222024,0.00099202,-0.00033067,-0.00165337,-0.00240920,-0.00344846,-0.00354294,-0.00340122,-0.00359017,-0.00340122,-0.00448772,-0.00552698,-0.00708587,-0.00864476,-0.00949507,-0.00977850,-0.00878648,-0.00751102,-0.00486563,-0.00273987,-0.00037791,0.00113374,0.00231472,0.00207852,0.00188957,0.00094478,0.00080307,0.00066135,0.00141717,0.00198404,0.00245644,0.00255091,0.00207852,0.00089754,0.00000000,-0.00155889,-0.00250367,-0.00354294,-0.00462944,-0.00519630,-0.00581041,-0.00571594,-0.00543250,-0.00420428,-0.00340122,-0.00184233,-0.00080307,0.00080307,0.00132270,0.00217300,0.00184233,0.00113374,0.00009448,-0.00127546,-0.00207852,-0.00264539,-0.00264539,-0.00250367,-0.00236196,-0.00165337,-0.00160613,-0.00070859,-0.00028343,0.00056687,0.00155889,0.00193680,0.00297607,0.00255091,0.00325950,0.00236196,0.00231472,0.00132270,0.00061411,-0.00023620,-0.00037791,-0.00018896,0.00099202,0.00226748,0.00344846,0.00425152,0.00363741,0.00307054,0.00108650,-0.00033067,-0.00184233,-0.00292883,-0.00349570,-0.00316502,-0.00354294,-0.00207852,-0.00264539,-0.00160613,-0.00141717,-0.00122822,-0.00023620,0.00023620,0.00151165,0.00240920,0.00292883,0.00349570,0.00292883,0.00278711,0.00136993,0.00070859,0.00042515,-0.00004724,0.00146441,0.00207852,0.00359017,0.00496011,0.00448772,0.00524354,0.00373189,0.00340122,0.00240920,0.00179509,0.00165337,0.00151165,0.00212576,0.00255091,0.00307054,0.00377913,0.00330674,0.00335398,0.00207852,0.00108650,-0.00028343,-0.00184233,-0.00259815,-0.00321226,-0.00264539,-0.00193680,-0.00037791,0.00094478,0.00212576,0.00278711,0.00264539,0.00203128,0.00108650,-0.00028343,-0.00118098,-0.00240920,-0.00311778,-0.00335398,-0.00382637,-0.00316502,-0.00292883,-0.00203128,-0.00103926,-0.00018896,0.00103926,0.00188957,0.00255091,0.00307054,0.00368465,0.00415704,0.00491287,0.00529078,0.00571594,0.00566870,0.00562146,0.00514907,0.00562146,0.00543250,0.00656624,0.00628280,0.00718035,0.00680244,0.00713311,0.00633004,0.00623557,0.00505459,0.00434600,0.00335398,0.00174785,0.00155889,0.00000000,-0.00004724,-0.00094478,-0.00165337,-0.00136993,-0.00146441,-0.00061411,0.00000000,0.00009448,-0.00004724,-0.00080307,-0.00165337,-0.00198404,-0.00136993,-0.00037791,0.00170061,0.00321226,0.00439324,0.00467667,0.00368465,0.00226748,0.00061411,-0.00141717,-0.00264539,-0.00382637,-0.00505459,-0.00557422,-0.00680244,-0.00732207,-0.00803065,-0.00798341,-0.00812513,-0.00708587,-0.00656624,-0.00514907,-0.00425152,-0.00340122,-0.00259815,-0.00226748,-0.00184233,-0.00151165,-0.00165337,-0.00146441,-0.00170061,-0.00179509,-0.00198404,-0.00203128,-0.00226748,-0.00146441,-0.00198404,-0.00047239,-0.00075583,0.00028343,0.00075583,0.00094478,0.00179509,0.00094478,0.00141717,0.00033067,0.00033067,0.00033067,0.00066135,0.00184233,0.00269263,0.00340122,0.00387361,0.00330674,0.00354294,0.00278711,0.00302330,0.00363741,0.00373189,0.00505459,0.00514907,0.00533802,0.00538526,0.00458220,0.00415704,0.00344846,0.00212576,0.00165337,0.00042515,-0.00009448,-0.00056687,-0.00094478,-0.00118098,-0.00136993,-0.00198404,-0.00231472,-0.00316502,-0.00330674,-0.00425152,-0.00406257,-0.00439324,-0.00401533,-0.00382637,-0.00321226,-0.00321226,-0.00273987,-0.00349570,-0.00311778,-0.00429876,-0.00401533,-0.00434600,-0.00429876,-0.00321226,-0.00382637,-0.00278711,-0.00335398,-0.00340122,-0.00368465,-0.00368465,-0.00382637,-0.00273987,-0.00283435,-0.00236196,-0.00250367,-0.00368465,-0.00377913,-0.00552698,-0.00481839,-0.00566870,-0.00458220,-0.00467667,-0.00392085,-0.00377913,-0.00368465,-0.00316502,-0.00278711,-0.00212576,-0.00155889,-0.00155889,-0.00089754,-0.00184233,-0.00132270,-0.00325950,-0.00330674,-0.00514907,-0.00581041,-0.00628280,-0.00595213,-0.00477115,-0.00307054,-0.00103926,0.00061411,0.00240920,0.00373189,0.00434600,0.00566870,0.00557422,0.00656624,0.00656624,0.00689691,0.00666072,0.00642452,0.00566870,0.00491287,0.00396809,0.00278711,0.00212576,0.00122822,0.00080307,0.00037791,0.00037791,0.00037791,0.00118098,0.00198404,0.00349570,0.00415704,0.00566870,0.00477115,0.00543250,0.00373189,0.00335398,0.00165337,0.00127546,0.00033067,0.00056687,0.00089754,0.00170061,0.00316502,0.00415704,0.00486563,0.00500735,0.00377913,0.00259815,0.00037791,-0.00141717,-0.00321226,-0.00377913,-0.00425152,-0.00340122,-0.00245644,-0.00165337,0.00004724,0.00037791,0.00141717,0.00165337,0.00184233,0.00160613,0.00151165,0.00108650,0.00066135,0.00155889,0.00122822,0.00325950,0.00392085,0.00543250,0.00623557,0.00689691,0.00670796,0.00708587,0.00604661,0.00637728,0.00552698,0.00519630,0.00524354,0.00354294,0.00368465,0.00136993,0.00056687,-0.00099202,-0.00231472,-0.00278711,-0.00325950,-0.00278711,-0.00264539,-0.00278711,-0.00283435,-0.00368465,-0.00425152,-0.00444048,-0.00382637,-0.00259815,-0.00009448,0.00141717,0.00349570,0.00392085,0.00368465,0.00335398,0.00146441,0.00066135,-0.00070859,-0.00198404,-0.00193680,-0.00273987,-0.00231472,-0.00132270,-0.00146441,0.00061411,0.00028343,0.00127546,0.00113374,0.00099202,0.00070859,0.00070859,0.00000000,0.00042515,0.00014172,0.00051963,0.00089754,0.00141717,0.00174785,0.00207852,0.00193680,0.00170061,0.00212576,0.00160613,0.00311778,0.00269263,0.00434600,0.00444048,0.00444048,0.00453496,0.00335398,0.00330674,0.00250367,0.00226748,0.00250367,0.00207852,0.00278711,0.00203128,0.00231472,0.00132270,0.00160613,0.00070859,0.00165337,0.00108650,0.00198404,0.00179509,0.00151165,0.00132270,0.00009448,-0.00075583,-0.00203128,-0.00330674,-0.00420428,-0.00467667,-0.00491287,-0.00410980,-0.00354294,-0.00212576,-0.00089754,0.00042515,0.00118098,0.00245644,0.00193680,0.00269263,0.00146441,0.00108650,0.00014172,-0.00028343,-0.00080307,-0.00051963,-0.00037791,-0.00004724,0.00066135,0.00099202,0.00141717,0.00198404,0.00207852,0.00292883,0.00335398,0.00486563,0.00505459,0.00599937,0.00519630,0.00486563,0.00325950,0.00288159,0.00136993,0.00240920,0.00198404,0.00359017,0.00363741,0.00552698,0.00543250,0.00718035,0.00703863,0.00788894,0.00798341,0.00788894,0.00769998,0.00666072,0.00609385,0.00458220,0.00406257,0.00316502,0.00288159,0.00245644,0.00217300,0.00136993,0.00075583,0.00023620,-0.00004724,0.00132270,0.00165337,0.00425152,0.00448772,0.00562146,0.00581041,0.00514907,0.00500735,0.00444048,0.00363741,0.00307054,0.00193680,0.00051963,-0.00023620,-0.00061411,0.00004724,0.00160613,0.00283435,0.00444048,0.00462944,0.00420428,0.00302330,0.00155889,-0.00014172,-0.00070859,-0.00226748,-0.00184233,-0.00302330,-0.00207852,-0.00273987,-0.00151165,-0.00160613,-0.00047239,-0.00056687,-0.00042515,-0.00080307,-0.00127546,-0.00198404,-0.00203128,-0.00273987,-0.00226748,-0.00236196,-0.00207852,-0.00184233,-0.00184233,-0.00155889,-0.00236196,-0.00212576,-0.00316502,-0.00250367,-0.00264539,-0.00184233,-0.00094478,-0.00061411,0.00037791,0.00066135,0.00075583,0.00070859,-0.00018896,-0.00094478,-0.00207852,-0.00283435,-0.00316502,-0.00392085,-0.00373189,-0.00444048,-0.00434600,-0.00439324,-0.00429876,-0.00401533,-0.00349570,-0.00349570,-0.00292883,-0.00302330,-0.00203128,-0.00165337,-0.00033067,0.00056687,0.00113374,0.00231472,0.00245644,0.00292883,0.00359017,0.00354294,0.00382637,0.00359017,0.00283435,0.00198404,0.00094478,-0.00004724,-0.00037791,-0.00113374,-0.00094478,-0.00155889,-0.00198404,-0.00292883,-0.00382637,-0.00505459,-0.00571594,-0.00599937,-0.00609385,-0.00585765,-0.00477115,-0.00496011,-0.00349570,-0.00359017,-0.00311778,-0.00259815,-0.00259815,-0.00212576,-0.00226748,-0.00198404,-0.00193680,-0.00207852,-0.00174785,-0.00217300,-0.00207852,-0.00255091,-0.00259815,-0.00255091,-0.00212576,-0.00127546,-0.00061411,0.00037791,0.00113374,0.00184233,0.00198404,0.00297607,0.00264539,0.00316502,0.00325950,0.00240920,0.00340122,0.00259815,0.00368465,0.00373189,0.00406257,0.00401533,0.00359017,0.00316502,0.00245644,0.00212576,0.00184233,0.00198404,0.00255091,0.00278711,0.00302330,0.00311778,0.00250367,0.00160613,0.00089754,-0.00066135,-0.00047239,-0.00179509,-0.00113374,-0.00193680,-0.00127546,-0.00155889,-0.00094478,-0.00056687,0.00004724,0.00094478,0.00118098,0.00207852,0.00170061,0.00174785,0.00127546,0.00047239,0.00047239,-0.00004724,-0.00004724,0.00018896,0.00042515,0.00113374,0.00198404,0.00250367,0.00382637,0.00359017,0.00420428,0.00349570,0.00278711,0.00222024,0.00113374,0.00127546,0.00160613,0.00269263,0.00392085,0.00543250,0.00618833,0.00666072,0.00614109,0.00562146,0.00406257,0.00330674,0.00203128,0.00094478,0.00000000,-0.00141717,-0.00250367,-0.00359017,-0.00382637,-0.00420428,-0.00316502,-0.00240920,-0.00141717,-0.00018896,-0.00009448,0.00037791,-0.00042515,-0.00047239,-0.00136993,-0.00089754,-0.00165337,-0.00051963,-0.00146441,-0.00113374,-0.00236196,-0.00359017,-0.00410980,-0.00576317,-0.00510183,-0.00566870,-0.00420428,-0.00325950,-0.00184233,-0.00066135,0.00033067,0.00075583,0.00089754,0.00108650,0.00066135,0.00094478,0.00127546,0.00184233,0.00283435,0.00354294,0.00429876,0.00458220,0.00420428,0.00330674,0.00222024,0.00056687,-0.00028343,-0.00118098,-0.00136993,-0.00099202,-0.00089754,-0.00014172,0.00037791,0.00080307,0.00136993,0.00174785,0.00236196,0.00335398,0.00415704,0.00581041,0.00675520,0.00812513,0.00836133,0.00798341,0.00689691,0.00496011,0.00363741,0.00170061,0.00165337,0.00075583,0.00160613,0.00132270,0.00184233,0.00108650,0.00070859,-0.00023620,-0.00113374,-0.00146441,-0.00179509,-0.00160613,-0.00094478,-0.00070859,0.00009448,0.00028343,0.00080307,0.00070859,0.00099202,0.00080307,0.00066135,0.00089754,0.00042515,0.00061411,-0.00018896,-0.00014172,-0.00141717,-0.00146441,-0.00269263,-0.00250367,-0.00311778,-0.00222024,-0.00207852,-0.00113374,-0.00042515,-0.00047239,0.00033067,-0.00075583,-0.00075583,-0.00165337,-0.00278711,-0.00292883,-0.00434600,-0.00354294,-0.00396809,-0.00240920,-0.00193680,-0.00028343,-0.00004724,0.00042515,-0.00014172,-0.00118098,-0.00231472,-0.00373189,-0.00491287,-0.00576317,-0.00647176,-0.00633004,-0.00647176,-0.00486563,-0.00434600,-0.00269263,-0.00146441,-0.00075583,0.00000000,0.00014172,-0.00037791,-0.00051963,-0.00118098,-0.00118098,-0.00118098,-0.00037791,0.00009448,0.00099202,0.00146441,0.00165337,0.00146441,0.00122822,0.00085030,0.00094478,0.00118098,0.00118098,0.00174785,0.00122822,0.00132270,0.00037791,0.00037791,-0.00051963,-0.00066135,-0.00132270,-0.00141717,-0.00174785,-0.00174785,-0.00222024,-0.00240920,-0.00325950,-0.00368465,-0.00420428,-0.00406257,-0.00359017,-0.00245644,-0.00136993,-0.00028343,0.00047239,0.00000000,-0.00018896,-0.00151165,-0.00198404,-0.00292883,-0.00226748,-0.00226748,-0.00094478,-0.00047239,0.00023620,0.00018896,0.00000000,-0.00075583,-0.00203128,-0.00288159,-0.00439324,-0.00467667,-0.00547974,-0.00467667,-0.00453496,-0.00321226,-0.00307054,-0.00231472,-0.00259815,-0.00264539,-0.00278711,-0.00307054,-0.00288159,-0.00330674,-0.00359017,-0.00396809,-0.00477115,-0.00496011,-0.00609385,-0.00547974,-0.00614109,-0.00481839,-0.00481839,-0.00307054,-0.00264539,-0.00108650,-0.00089754,0.00014172,0.00000000,0.00033067,-0.00047239,-0.00099202,-0.00136993,-0.00236196,-0.00184233,-0.00170061,-0.00075583,0.00047239,0.00113374,0.00212576,0.00203128,0.00231472,0.00132270,0.00066135,-0.00028343,-0.00118098,-0.00165337,-0.00193680,-0.00146441,-0.00099202,-0.00066135,0.00056687,0.00033067,0.00184233,0.00127546,0.00198404,0.00118098,0.00122822,0.00061411,0.00033067,0.00033067,0.00023620,0.00018896,-0.00004724,-0.00089754,-0.00146441,-0.00250367,-0.00240920,-0.00236196,-0.00151165,-0.00023620,0.00085030,0.00193680,0.00269263,0.00250367,0.00297607,0.00231472,0.00207852,0.00160613,0.00099202,0.00094478,0.00042515,0.00028343,-0.00061411,-0.00108650,-0.00212576,-0.00283435,-0.00368465,-0.00420428,-0.00406257,-0.00439324,-0.00349570,-0.00344846,-0.00259815,-0.00217300,-0.00207852,-0.00188957,-0.00226748,-0.00250367,-0.00307054,-0.00321226,-0.00311778,-0.00311778,-0.00236196,-0.00278711,-0.00193680,-0.00269263,-0.00207852,-0.00240920,-0.00155889,-0.00075583,0.00047239,0.00160613,0.00264539,0.00349570,0.00335398,0.00363741,0.00288159,0.00245644,0.00207852,0.00122822,0.00094478,-0.00023620,-0.00037791,-0.00174785,-0.00141717,-0.00250367,-0.00184233,-0.00198404,-0.00155889,-0.00146441,-0.00170061,-0.00151165,-0.00236196,-0.00188957,-0.00231472,-0.00165337,-0.00108650,-0.00004724,0.00061411,0.00212576,0.00198404,0.00316502,0.00259815,0.00292883,0.00203128,0.00207852,0.00080307,0.00056687,-0.00037791,-0.00037791,-0.00047239,-0.00014172,0.00023620,0.00028343,0.00099202,0.00085030,0.00160613,0.00136993,0.00170061,0.00146441,0.00127546,0.00099202,0.00033067,0.00014172,-0.00018896,0.00051963,0.00056687,0.00170061,0.00203128,0.00273987,0.00226748,0.00203128,0.00089754,-0.00033067,-0.00113374,-0.00288159,-0.00278711,-0.00349570,-0.00311778,-0.00198404,-0.00108650,0.00113374,0.00222024,0.00434600,0.00467667,0.00581041,0.00533802,0.00434600,0.00349570,0.00132270,0.00075583,-0.00028343,-0.00033067,0.00023620,0.00014172,0.00094478,0.00051963,0.00042515,0.00014172,-0.00061411,-0.00047239,-0.00108650,-0.00080307,-0.00070859,-0.00018896,0.00009448,0.00127546,0.00127546,0.00307054,0.00259815,0.00340122,0.00207852,0.00075583,-0.00094478,-0.00307054,-0.00458220,-0.00533802,-0.00538526,-0.00373189,-0.00212576,0.00061411,0.00316502,0.00510183,0.00694415,0.00699139,0.00689691,0.00576317,0.00477115,0.00349570,0.00288159,0.00170061,0.00165337,0.00089754,0.00047239,0.00061411,0.00004724,0.00094478,0.00070859,0.00198404,0.00188957,0.00344846,0.00278711,0.00382637,0.00278711,0.00321226,0.00217300,0.00165337,0.00099202,-0.00028343,-0.00061411,-0.00174785,-0.00170061,-0.00226748,-0.00136993,-0.00179509,-0.00122822,-0.00184233,-0.00222024,-0.00297607,-0.00335398,-0.00392085,-0.00340122,-0.00321226,-0.00193680,-0.00146441,-0.00033067,0.00009448,0.00037791,0.00089754,0.00089754,0.00118098,0.00146441,0.00174785,0.00160613,0.00207852,0.00160613,0.00174785,0.00085030,0.00004724,-0.00103926,-0.00217300,-0.00278711,-0.00297607,-0.00264539,-0.00141717,0.00009448,0.00146441,0.00354294,0.00377913,0.00472391,0.00330674,0.00264539,0.00051963,-0.00061411,-0.00222024,-0.00278711,-0.00340122,-0.00292883,-0.00302330,-0.00207852,-0.00198404,-0.00136993,-0.00127546,-0.00089754,-0.00103926,-0.00061411,-0.00075583,-0.00099202,-0.00094478,-0.00146441,-0.00122822,-0.00056687,0.00009448,0.00151165,0.00198404,0.00292883,0.00278711,0.00321226,0.00273987,0.00292883,0.00250367,0.00255091,0.00160613,0.00160613,0.00018896,-0.00004724,-0.00080307,-0.00118098,-0.00056687,-0.00037791,0.00080307,0.00188957,0.00222024,0.00311778,0.00240920,0.00203128,0.00061411,-0.00037791,-0.00188957,-0.00255091,-0.00307054,-0.00297607,-0.00203128,-0.00118098,-0.00023620,0.00099202,0.00151165,0.00250367,0.00212576,0.00269263,0.00132270,0.00146441,0.00000000,-0.00023620,-0.00127546,-0.00113374,-0.00151165,-0.00089754,-0.00066135,0.00004724,0.00075583,0.00122822,0.00193680,0.00151165,0.00236196,0.00118098,0.00155889,0.00070859,0.00028343,0.00023620,0.00004724,0.00023620,0.00066135,0.00056687,0.00099202,0.00089754,0.00099202,0.00103926,0.00099202,0.00099202,0.00070859,0.00061411,0.00037791,0.00089754,0.00146441,0.00231472,0.00307054,0.00330674,0.00349570,0.00292883,0.00250367,0.00179509,0.00108650,0.00127546,0.00103926,0.00188957,0.00203128,0.00226748,0.00188957,0.00122822,0.00009448,-0.00113374,-0.00217300,-0.00307054,-0.00363741,-0.00396809,-0.00429876,-0.00410980,-0.00401533,-0.00255091,-0.00217300,0.00004724,0.00023620,0.00179509,0.00226748,0.00273987,0.00316502,0.00392085,0.00377913,0.00462944,0.00392085,0.00401533,0.00363741,0.00302330,0.00311778,0.00259815,0.00240920,0.00203128,0.00141717,0.00099202,0.00061411,-0.00004724,0.00018896,-0.00051963,0.00051963,0.00051963,0.00193680,0.00255091,0.00406257,0.00444048,0.00486563,0.00505459,0.00387361,0.00387361,0.00269263,0.00231472,0.00193680,0.00160613,0.00155889,0.00122822,0.00113374,0.00085030,0.00085030,0.00085030,0.00127546,0.00146441,0.00198404,0.00245644,0.00231472,0.00321226,0.00222024,0.00340122,0.00193680,0.00245644,0.00151165,0.00151165,0.00118098,0.00146441,0.00094478,0.00061411,-0.00004724,-0.00122822,-0.00236196,-0.00340122,-0.00472391,-0.00481839,-0.00557422,-0.00500735,-0.00491287,-0.00387361,-0.00283435,-0.00141717,-0.00066135,0.00047239,0.00061411,0.00037791,0.00023620,-0.00085030,-0.00099202,-0.00174785,-0.00179509,-0.00222024,-0.00245644,-0.00283435,-0.00335398,-0.00363741,-0.00368465,-0.00363741,-0.00288159,-0.00222024,-0.00155889,-0.00118098,-0.00136993,-0.00141717,-0.00198404,-0.00217300,-0.00170061,-0.00113374,0.00000000,0.00132270,0.00170061,0.00231472,0.00222024,0.00212576,0.00198404,0.00193680,0.00207852,0.00240920,0.00321226,0.00363741,0.00420428,0.00453496,0.00491287,0.00467667,0.00472391,0.00392085,0.00373189,0.00359017,0.00354294,0.00396809,0.00439324,0.00491287,0.00552698,0.00562146,0.00486563,0.00363741,0.00170061,-0.00075583,-0.00255091,-0.00444048,-0.00486563,-0.00453496,-0.00307054,-0.00160613,0.00089754,0.00231472,0.00307054,0.00359017,0.00212576,0.00094478,-0.00132270,-0.00311778,-0.00439324,-0.00505459,-0.00500735,-0.00448772,-0.00354294,-0.00250367,-0.00155889,-0.00047239,-0.00028343,0.00014172,-0.00018896,-0.00075583,-0.00170061,-0.00283435,-0.00387361,-0.00500735,-0.00510183,-0.00571594,-0.00448772,-0.00410980,-0.00283435,-0.00222024,-0.00160613,-0.00155889,-0.00155889,-0.00198404,-0.00240920,-0.00264539,-0.00288159,-0.00321226,-0.00344846,-0.00354294,-0.00349570,-0.00321226,-0.00250367,-0.00212576,-0.00061411,-0.00014172,0.00103926,0.00108650,0.00170061,0.00108650,0.00127546,0.00009448,0.00009448,-0.00047239,-0.00070859,-0.00066135,-0.00037791,0.00004724,0.00070859,0.00113374,0.00165337,0.00184233,0.00165337,0.00099202,0.00018896,-0.00042515,-0.00151165,-0.00165337,-0.00231472,-0.00231472,-0.00231472,-0.00259815,-0.00330674,-0.00344846,-0.00453496,-0.00406257,-0.00377913,-0.00236196,-0.00037791,0.00151165,0.00373189,0.00439324,0.00547974,0.00420428,0.00382637,0.00207852,0.00089754,-0.00018896,-0.00037791,-0.00070859,0.00061411,0.00023620,0.00155889,0.00066135,0.00061411,-0.00099202,-0.00198404,-0.00292883,-0.00307054,-0.00269263,-0.00179509,-0.00066135,0.00028343,0.00132270,0.00132270,0.00193680,0.00160613,0.00203128,0.00203128,0.00222024,0.00240920,0.00165337,0.00108650,0.00004724,-0.00179509,-0.00255091,-0.00439324,-0.00410980,-0.00462944,-0.00373189,-0.00292883,-0.00165337,-0.00047239,0.00056687,0.00094478,0.00170061,0.00170061,0.00222024,0.00245644,0.00278711,0.00292883,0.00283435,0.00207852,0.00207852,0.00136993,0.00146441,0.00146441,0.00113374,0.00165337,0.00066135,0.00051963,-0.00033067,-0.00066135,-0.00099202,-0.00103926,-0.00103926,-0.00075583,-0.00099202,-0.00066135,-0.00127546,-0.00085030,-0.00141717,-0.00066135,-0.00108650,-0.00009448,-0.00009448,0.00033067,0.00113374,0.00066135,0.00212576,0.00122822,0.00250367,0.00222024,0.00283435,0.00363741,0.00387361,0.00462944,0.00500735,0.00491287,0.00538526,0.00472391,0.00401533,0.00311778,0.00155889,0.00014172,-0.00118098,-0.00207852,-0.00231472,-0.00151165,-0.00113374,0.00122822,0.00141717,0.00363741,0.00344846,0.00406257,0.00382637,0.00330674,0.00278711,0.00269263,0.00193680,0.00212576,0.00155889,0.00179509,0.00160613,0.00179509,0.00122822,0.00108650,0.00028343,-0.00018896,-0.00014172,-0.00014172,0.00094478,0.00160613,0.00283435,0.00359017,0.00401533,0.00477115,0.00448772,0.00472391,0.00377913,0.00325950,0.00240920,0.00141717,0.00094478,-0.00004724,-0.00037791,-0.00075583,-0.00089754,-0.00075583,-0.00051963,0.00000000,-0.00009448,-0.00014172,-0.00056687,-0.00122822,-0.00170061,-0.00151165,-0.00170061,-0.00108650,-0.00066135,-0.00085030,-0.00056687,-0.00089754,-0.00113374,-0.00051963,-0.00042515,0.00051963,0.00108650,0.00141717,0.00146441,0.00094478,0.00023620,-0.00103926,-0.00207852,-0.00392085,-0.00514907,-0.00670796,-0.00840857,-0.00921163,-0.01043985,-0.01119567,-0.01119567,-0.01143187,-0.01029813,-0.00921163,-0.00779446,-0.00618833,-0.00538526,-0.00448772,-0.00401533,-0.00377913,-0.00335398,-0.00245644,-0.00231472,-0.00070859,-0.00094478,0.00070859,0.00023620,0.00174785,0.00165337,0.00311778,0.00325950,0.00434600,0.00439324,0.00458220,0.00420428,0.00325950,0.00231472,0.00146441,0.00023620,-0.00018896,-0.00070859,-0.00099202,-0.00061411,-0.00118098,-0.00056687,-0.00136993,-0.00066135,-0.00122822,-0.00094478,-0.00042515,-0.00033067,0.00056687,0.00085030,0.00103926,0.00146441,0.00094478,0.00056687,0.00004724,-0.00155889,-0.00188957,-0.00335398,-0.00363741,-0.00349570,-0.00368465,-0.00212576,-0.00217300,-0.00132270,-0.00136993,-0.00151165,-0.00141717,-0.00113374,-0.00047239,0.00075583,0.00146441,0.00198404,0.00198404,0.00146441,0.00080307,0.00051963,-0.00051963,0.00009448,-0.00108650,-0.00047239,-0.00136993,-0.00094478,-0.00103926,-0.00080307,-0.00037791,-0.00047239,0.00004724,0.00004724,0.00028343,0.00080307,0.00094478,0.00198404,0.00231472,0.00311778,0.00354294,0.00349570,0.00311778,0.00226748,0.00089754,0.00000000,-0.00136993,-0.00207852,-0.00226748,-0.00311778,-0.00264539,-0.00325950,-0.00316502,-0.00273987,-0.00359017,-0.00292883,-0.00392085,-0.00392085,-0.00406257,-0.00462944,-0.00363741,-0.00368465,-0.00255091,-0.00217300,-0.00179509,-0.00151165,-0.00184233,-0.00231472,-0.00278711,-0.00311778,-0.00335398,-0.00330674,-0.00340122,-0.00335398,-0.00330674,-0.00344846,-0.00311778,-0.00283435,-0.00188957,-0.00146441,-0.00009448,0.00051963,0.00184233,0.00264539,0.00349570,0.00406257,0.00410980,0.00420428,0.00283435,0.00236196,-0.00023620,-0.00080307,-0.00344846,-0.00377913,-0.00519630,-0.00514907,-0.00496011,-0.00477115,-0.00420428,-0.00354294,-0.00330674,-0.00259815,-0.00231472,-0.00222024,-0.00179509,-0.00170061,-0.00188957,-0.00155889,-0.00212576,-0.00193680,-0.00203128,-0.00174785,-0.00203128,-0.00122822,-0.00160613,-0.00075583,-0.00070859,-0.00009448,0.00047239,0.00122822,0.00188957,0.00255091,0.00335398,0.00377913,0.00425152,0.00420428,0.00406257,0.00392085,0.00340122,0.00349570,0.00307054,0.00335398,0.00321226,0.00311778,0.00283435,0.00184233,0.00127546,-0.00014172,-0.00113374,-0.00222024,-0.00307054,-0.00344846,-0.00377913,-0.00354294,-0.00321226,-0.00259815,-0.00165337,-0.00061411,0.00070859,0.00240920,0.00392085,0.00571594,0.00614109,0.00689691,0.00609385,0.00538526,0.00434600,0.00307054,0.00207852,0.00155889,0.00018896,0.00023620,-0.00080307,-0.00014172,0.00037791,0.00155889,0.00330674,0.00448772,0.00519630,0.00562146,0.00425152,0.00349570,0.00160613,-0.00018896,-0.00127546,-0.00283435,-0.00269263,-0.00316502,-0.00212576,-0.00207852,-0.00118098,-0.00118098,-0.00160613,-0.00188957,-0.00311778,-0.00368465,-0.00420428,-0.00481839,-0.00420428,-0.00420428,-0.00335398,-0.00307054,-0.00264539,-0.00226748,-0.00212576,-0.00146441,-0.00132270,-0.00108650,-0.00108650,-0.00179509,-0.00250367,-0.00325950,-0.00368465,-0.00335398,-0.00269263,-0.00146441,-0.00080307,0.00023620,0.00009448,0.00033067,-0.00018896,-0.00004724,-0.00042515,-0.00023620,-0.00061411,-0.00066135,-0.00089754,-0.00085030,-0.00165337,-0.00146441,-0.00302330,-0.00231472,-0.00363741,-0.00269263,-0.00264539,-0.00136993,-0.00051963,0.00033067,0.00108650,0.00136993,0.00132270,0.00165337,0.00118098,0.00170061,0.00174785,0.00198404,0.00264539,0.00236196,0.00273987,0.00207852,0.00146441,0.00056687,-0.00099202,-0.00203128,-0.00368465,-0.00434600,-0.00576317,-0.00618833,-0.00675520,-0.00684967,-0.00713311,-0.00647176,-0.00699139,-0.00547974,-0.00590489,-0.00496011,-0.00496011,-0.00491287,-0.00453496,-0.00453496,-0.00429876,-0.00387361,-0.00363741,-0.00359017,-0.00288159,-0.00259815,-0.00146441,-0.00009448,0.00099202,0.00259815,0.00344846,0.00415704,0.00429876,0.00363741,0.00269263,0.00155889,0.00066135,-0.00014172,-0.00080307,-0.00099202,-0.00146441,-0.00132270,-0.00151165,-0.00113374,-0.00075583,-0.00023620,0.00075583,0.00155889,0.00264539,0.00354294,0.00396809,0.00514907,0.00496011,0.00604661,0.00604661,0.00684967,0.00694415,0.00684967,0.00651900,0.00514907,0.00410980,0.00222024,0.00080307,-0.00047239,-0.00108650,-0.00113374,-0.00033067,0.00056687,0.00151165,0.00240920,0.00283435,0.00302330,0.00307054,0.00292883,0.00231472,0.00198404,0.00108650,0.00070859,-0.00014172,0.00018896,-0.00033067,0.00061411,0.00089754,0.00118098,0.00179509,0.00151165,0.00198404,0.00141717,0.00146441,0.00118098,0.00094478,0.00075583,0.00051963,-0.00042515,-0.00070859,-0.00226748,-0.00292883,-0.00434600,-0.00434600,-0.00486563,-0.00359017,-0.00255091,-0.00094478,0.00018896,0.00066135,0.00099202,0.00014172,-0.00004724,-0.00047239,0.00000000,0.00165337,0.00264539,0.00505459,0.00514907,0.00604661,0.00420428,0.00316502,0.00000000,-0.00127546,-0.00415704,-0.00477115,-0.00614109,-0.00604661,-0.00590489,-0.00510183,-0.00406257,-0.00273987,-0.00122822,0.00018896,0.00160613,0.00255091,0.00340122,0.00354294,0.00410980,0.00354294,0.00382637,0.00283435,0.00250367,0.00155889,0.00042515,-0.00075583,-0.00179509,-0.00316502,-0.00349570,-0.00429876,-0.00373189,-0.00335398,-0.00155889,-0.00089754,0.00080307,0.00108650,0.00151165,0.00103926,0.00066135,-0.00042515,-0.00066135,-0.00080307,-0.00103926,-0.00004724,-0.00028343,0.00056687,0.00037791,-0.00033067,-0.00037791,-0.00198404,-0.00231472,-0.00335398,-0.00377913,-0.00292883,-0.00240920,-0.00085030,0.00066135,0.00174785,0.00288159,0.00259815,0.00231472,0.00132270,0.00023620,0.00004724,-0.00004724,0.00075583,0.00160613,0.00259815,0.00273987,0.00311778,0.00226748,0.00174785,0.00113374,0.00056687,0.00047239,0.00042515,0.00042515,0.00080307,0.00075583,0.00132270,0.00170061,0.00207852,0.00311778,0.00302330,0.00359017,0.00307054,0.00273987,0.00170061,0.00132270,0.00061411,0.00056687,0.00094478,0.00099202,0.00132270,0.00193680,0.00108650,0.00250367,0.00170061,0.00325950,0.00349570,0.00410980,0.00453496,0.00439324,0.00392085,0.00288159,0.00184233,0.00018896,-0.00056687,-0.00160613,-0.00222024,-0.00203128,-0.00207852,-0.00132270,-0.00061411,-0.00047239,0.00028343,-0.00004724,-0.00023620,-0.00061411,-0.00085030,-0.00108650,-0.00099202,-0.00113374,-0.00141717,-0.00160613,-0.00151165,-0.00193680,-0.00103926,-0.00089754,-0.00051963,0.00028343,-0.00075583,-0.00009448,-0.00146441,-0.00132270,-0.00203128,-0.00170061,-0.00122822,-0.00042515,0.00056687,0.00151165,0.00198404,0.00226748,0.00259815,0.00231472,0.00259815,0.00264539,0.00259815,0.00250367,0.00283435,0.00184233,0.00278711,0.00212576,0.00302330,0.00330674,0.00363741,0.00349570,0.00368465,0.00292883,0.00316502,0.00198404,0.00226748,0.00132270,0.00184233,0.00113374,0.00160613,0.00075583,0.00047239,-0.00066135,-0.00217300,-0.00377913,-0.00533802,-0.00609385,-0.00651900,-0.00543250,-0.00453496,-0.00255091,-0.00118098,0.00004724,0.00066135,0.00042515,0.00037791,-0.00066135,-0.00113374,-0.00184233,-0.00255091,-0.00283435,-0.00321226,-0.00330674,-0.00316502,-0.00288159,-0.00278711,-0.00245644,-0.00283435,-0.00297607,-0.00373189,-0.00382637,-0.00429876,-0.00434600,-0.00448772,-0.00486563,-0.00491287,-0.00552698,-0.00500735,-0.00491287,-0.00373189,-0.00255091,-0.00118098,0.00042515,0.00151165,0.00222024,0.00259815,0.00240920,0.00240920,0.00188957,0.00217300,0.00184233,0.00273987,0.00316502,0.00444048,0.00543250,0.00633004,0.00708587,0.00708587,0.00694415,0.00590489,0.00514907,0.00415704,0.00325950,0.00292883,0.00212576,0.00245644,0.00222024,0.00240920,0.00264539,0.00288159,0.00264539,0.00321226,0.00188957,0.00207852,0.00051963,0.00004724,-0.00085030,-0.00141717,-0.00061411,-0.00103926,0.00075583,0.00051963,0.00203128,0.00165337,0.00203128,0.00136993,0.00042515,-0.00009448,-0.00198404,-0.00188957,-0.00340122,-0.00283435,-0.00335398,-0.00269263,-0.00259815,-0.00141717,-0.00132270,0.00047239,0.00080307,0.00212576,0.00269263,0.00278711,0.00302330,0.00245644,0.00231472,0.00174785,0.00170061,0.00146441,0.00165337,0.00136993,0.00113374,0.00023620,-0.00014172,-0.00089754,-0.00047239,-0.00014172,0.00089754,0.00193680,0.00255091,0.00321226,0.00335398,0.00292883,0.00316502,0.00193680,0.00193680,0.00080307,0.00023620,-0.00023620,-0.00146441,-0.00136993,-0.00236196,-0.00231472,-0.00283435,-0.00283435,-0.00321226,-0.00311778,-0.00288159,-0.00283435,-0.00217300,-0.00170061,-0.00122822,-0.00108650,-0.00085030,-0.00198404,-0.00174785,-0.00330674,-0.00344846,-0.00448772,-0.00505459,-0.00538526,-0.00552698,-0.00491287,-0.00410980,-0.00283435,-0.00151165,-0.00037791,0.00075583,0.00174785,0.00193680,0.00269263,0.00240920,0.00231472,0.00170061,0.00094478,-0.00037791,-0.00103926,-0.00203128,-0.00316502,-0.00269263,-0.00401533,-0.00273987,-0.00368465,-0.00259815,-0.00278711,-0.00203128,-0.00226748,-0.00203128,-0.00273987,-0.00302330,-0.00425152,-0.00439324,-0.00557422,-0.00505459,-0.00481839,-0.00387361,-0.00207852,-0.00094478,0.00094478,0.00184233,0.00283435,0.00321226,0.00354294,0.00344846,0.00396809,0.00392085,0.00420428,0.00415704,0.00387361,0.00283435,0.00236196,0.00037791,-0.00089754,-0.00217300,-0.00387361,-0.00387361,-0.00486563,-0.00453496,-0.00481839,-0.00477115,-0.00500735,-0.00496011,-0.00491287,-0.00444048,-0.00363741,-0.00250367,-0.00146441,-0.00023620,-0.00014172,0.00089754,0.00042515,0.00108650,0.00118098,0.00103926,0.00188957,0.00132270,0.00165337,0.00151165,0.00103926,0.00165337,0.00136993,0.00231472,0.00278711,0.00354294,0.00415704,0.00458220,0.00500735,0.00458220,0.00486563,0.00392085,0.00425152,0.00335398,0.00288159,0.00222024,0.00103926,0.00066135,-0.00042515,-0.00042515,-0.00023620,0.00047239,0.00165337,0.00264539,0.00316502,0.00349570,0.00316502,0.00198404,0.00146441,0.00009448,-0.00014172,-0.00070859,-0.00056687,-0.00033067,0.00028343,0.00127546,0.00207852,0.00292883,0.00373189,0.00354294,0.00359017,0.00255091,0.00184233,0.00070859,0.00075583,0.00018896,0.00108650,0.00193680,0.00302330,0.00406257,0.00462944,0.00420428,0.00406257,0.00245644,0.00170061,0.00023620,-0.00103926,-0.00170061,-0.00316502,-0.00311778,-0.00396809,-0.00340122,-0.00302330,-0.00222024,-0.00103926,-0.00056687,-0.00004724,-0.00033067,-0.00085030,-0.00222024,-0.00283435,-0.00420428,-0.00453496,-0.00462944,-0.00429876,-0.00288159,-0.00240920,-0.00056687,0.00014172,0.00160613,0.00222024,0.00288159,0.00278711,0.00240920,0.00179509,0.00056687,-0.00009448,-0.00108650,-0.00118098,-0.00075583,-0.00037791,0.00000000,0.00023620,-0.00051963,-0.00009448,-0.00170061,-0.00099202,-0.00250367,-0.00141717,-0.00222024,-0.00118098,-0.00179509,-0.00108650,-0.00127546,-0.00037791,-0.00009448,0.00132270,0.00132270,0.00288159,0.00288159,0.00340122,0.00382637,0.00344846,0.00359017,0.00302330,0.00245644,0.00155889,0.00028343,-0.00051963,-0.00193680,-0.00217300,-0.00297607,-0.00330674,-0.00377913,-0.00354294,-0.00373189,-0.00259815,-0.00184233,-0.00023620,0.00146441,0.00250367,0.00382637,0.00396809,0.00425152,0.00420428,0.00354294,0.00330674,0.00340122,0.00278711,0.00382637,0.00307054,0.00373189,0.00330674,0.00292883,0.00255091,0.00146441,0.00122822,0.00033067,-0.00042515,-0.00085030,-0.00203128,-0.00273987,-0.00359017,-0.00439324,-0.00481839,-0.00481839,-0.00448772,-0.00359017,-0.00264539,-0.00160613,-0.00061411,0.00000000,0.00108650,0.00132270,0.00231472,0.00226748,0.00240920,0.00193680,0.00132270,0.00066135,0.00042515,-0.00018896,0.00047239,0.00066135,0.00132270,0.00236196,0.00245644,0.00363741,0.00340122,0.00401533,0.00359017,0.00354294,0.00316502,0.00179509,0.00127546,-0.00118098,-0.00165337,-0.00330674,-0.00325950,-0.00340122,-0.00273987,-0.00174785,-0.00151165,-0.00061411,-0.00127546,-0.00141717,-0.00255091,-0.00307054,-0.00444048,-0.00434600,-0.00510183,-0.00505459,-0.00458220,-0.00500735,-0.00373189,-0.00458220,-0.00292883,-0.00368465,-0.00250367,-0.00226748,-0.00188957,-0.00089754,-0.00094478,-0.00033067,-0.00042515,0.00023620,0.00014172,0.00037791,0.00037791,-0.00004724,-0.00018896,-0.00033067,-0.00066135,-0.00004724,-0.00023620,0.00037791,0.00023620,-0.00004724,-0.00033067,-0.00118098,-0.00170061,-0.00184233,-0.00188957,-0.00080307,0.00004724,0.00184233,0.00259815,0.00382637,0.00373189,0.00406257,0.00363741,0.00401533,0.00330674,0.00377913,0.00264539,0.00325950,0.00198404,0.00278711,0.00231472,0.00302330,0.00349570,0.00396809,0.00406257,0.00415704,0.00415704,0.00349570,0.00344846,0.00321226,0.00283435,0.00377913,0.00392085,0.00477115,0.00529078,0.00557422,0.00533802,0.00524354,0.00406257,0.00354294,0.00226748,0.00151165,0.00070859,-0.00018896,0.00014172,-0.00089754,-0.00004724,-0.00099202,-0.00075583,-0.00136993,-0.00170061,-0.00203128,-0.00278711,-0.00269263,-0.00316502,-0.00297607,-0.00297607,-0.00321226,-0.00292883,-0.00231472,-0.00184233,-0.00023620,0.00047239,0.00207852,0.00255091,0.00307054,0.00307054,0.00255091,0.00278711,0.00222024,0.00217300,0.00222024,0.00136993,0.00174785,0.00103926,0.00141717,0.00136993,0.00132270,0.00118098,0.00103926,0.00014172,0.00018896,-0.00075583,-0.00023620,-0.00075583,0.00000000,-0.00042515,0.00042515,0.00000000,0.00033067,0.00009448,0.00014172,0.00018896,-0.00014172,-0.00009448,-0.00047239,-0.00037791,-0.00070859,-0.00122822,-0.00108650,-0.00155889,-0.00103926,-0.00094478,-0.00108650,-0.00085030,-0.00141717,-0.00151165,-0.00198404,-0.00160613,-0.00146441,-0.00066135,-0.00018896,0.00037791,0.00080307,0.00037791,0.00075583,-0.00028343,-0.00004724,-0.00070859,-0.00094478,-0.00094478,-0.00108650,-0.00094478,-0.00113374,-0.00146441,-0.00193680,-0.00250367,-0.00269263,-0.00264539,-0.00255091,-0.00207852,-0.00203128,-0.00141717,-0.00151165,-0.00075583,-0.00132270,-0.00033067,-0.00132270,-0.00066135,-0.00160613,-0.00165337,-0.00146441,-0.00165337,-0.00075583,-0.00037791,-0.00023620,0.00004724,-0.00018896,-0.00037791,0.00033067,0.00028343,0.00179509,0.00198404,0.00316502,0.00269263,0.00250367,0.00132270,-0.00028343,-0.00184233,-0.00373189,-0.00477115,-0.00505459,-0.00519630,-0.00340122,-0.00245644,0.00014172,0.00222024,0.00444048,0.00680244,0.00793617,0.00935335,0.00883372,0.00859752,0.00656624,0.00425152,0.00222024,-0.00089754,-0.00160613,-0.00302330,-0.00179509,-0.00080307,0.00151165,0.00288159,0.00467667,0.00477115,0.00491287,0.00406257,0.00236196,0.00085030,-0.00160613,-0.00330674,-0.00486563,-0.00529078,-0.00472391,-0.00377913,-0.00198404,-0.00047239,0.00047239,0.00184233,0.00170061,0.00269263,0.00245644,0.00307054,0.00264539,0.00292883,0.00278711,0.00311778,0.00368465,0.00396809,0.00458220,0.00467667,0.00425152,0.00363741,0.00255091,0.00165337,0.00170061,0.00207852,0.00325950,0.00505459,0.00566870,0.00623557,0.00481839,0.00307054,0.00089754,-0.00184233,-0.00316502,-0.00462944,-0.00500735,-0.00462944,-0.00363741,-0.00269263,-0.00033067,0.00103926,0.00245644,0.00401533,0.00401533,0.00444048,0.00359017,0.00307054,0.00127546,0.00023620,-0.00179509,-0.00311778,-0.00444048,-0.00557422,-0.00623557,-0.00694415,-0.00741654,-0.00774722,-0.00779446,-0.00755826,-0.00755826,-0.00689691,-0.00732207,-0.00628280,-0.00680244,-0.00552698,-0.00505459,-0.00387361,-0.00278711,-0.00184233,-0.00127546,-0.00037791,-0.00051963,-0.00014172,0.00028343,0.00000000,0.00113374,0.00099202,0.00184233,0.00193680,0.00160613,0.00155889,0.00028343,0.00009448,-0.00141717,-0.00151165,-0.00273987,-0.00236196,-0.00278711,-0.00193680,-0.00108650,0.00014172,0.00127546,0.00240920,0.00259815,0.00255091,0.00146441,0.00033067,-0.00179509,-0.00288159,-0.00458220,-0.00500735,-0.00514907,-0.00481839,-0.00344846,-0.00278711,-0.00151165,-0.00103926,-0.00118098,-0.00127546,-0.00188957,-0.00311778,-0.00325950,-0.00458220,-0.00425152,-0.00453496,-0.00392085,-0.00382637,-0.00335398,-0.00302330,-0.00259815,-0.00155889,-0.00047239,0.00099202,0.00198404,0.00316502,0.00273987,0.00311778,0.00179509,0.00136993,0.00066135,-0.00014172,0.00014172,-0.00056687,-0.00042515,-0.00056687,-0.00094478,-0.00113374,-0.00108650,-0.00165337,-0.00089754,-0.00174785,-0.00155889,-0.00222024,-0.00250367,-0.00250367,-0.00250367,-0.00155889,-0.00080307,0.00085030,0.00207852,0.00316502,0.00415704,0.00444048,0.00491287,0.00496011,0.00519630,0.00467667,0.00519630,0.00387361,0.00387361,0.00240920,0.00174785,0.00089754,0.00066135,0.00094478,0.00141717,0.00217300,0.00283435,0.00377913,0.00434600,0.00514907,0.00547974,0.00547974,0.00562146,0.00472391,0.00453496,0.00354294,0.00330674,0.00259815,0.00198404,0.00151165,0.00085030,0.00042515,0.00018896,0.00000000,0.00033067,0.00066135,0.00066135,0.00070859,0.00042515,-0.00004724,-0.00056687,-0.00070859,-0.00094478,-0.00042515,-0.00004724,-0.00018896,0.00033067,-0.00066135,-0.00108650,-0.00212576,-0.00311778,-0.00359017,-0.00401533,-0.00373189,-0.00283435,-0.00212576,-0.00061411,0.00037791,0.00170061,0.00250367,0.00354294,0.00425152,0.00491287,0.00543250,0.00557422,0.00590489,0.00576317,0.00604661,0.00543250,0.00510183,0.00472391,0.00349570,0.00373189,0.00217300,0.00273987,0.00174785,0.00212576,0.00170061,0.00212576,0.00207852,0.00273987,0.00330674,0.00439324,0.00500735,0.00628280,0.00656624,0.00694415,0.00694415,0.00604661,0.00524354,0.00396809,0.00292883,0.00231472,0.00207852,0.00269263,0.00255091,0.00377913,0.00354294,0.00387361,0.00373189,0.00349570,0.00368465,0.00396809,0.00477115,0.00524354,0.00614109,0.00566870,0.00514907,0.00359017,0.00165337,-0.00037791,-0.00207852,-0.00344846,-0.00311778,-0.00264539,-0.00042515,0.00146441,0.00439324,0.00595213,0.00831409,0.00807789,0.00869200,0.00755826,0.00666072,0.00576317,0.00505459,0.00467667,0.00510183,0.00462944,0.00529078,0.00434600,0.00462944,0.00330674,0.00264539,0.00141717,-0.00009448,-0.00108650,-0.00222024,-0.00269263,-0.00269263,-0.00226748,-0.00141717,-0.00051963,-0.00009448,0.00061411,0.00042515,0.00051963,0.00014172,-0.00051963,-0.00070859,-0.00188957,-0.00160613,-0.00288159,-0.00207852,-0.00273987,-0.00165337,-0.00108650,-0.00037791,0.00113374,0.00193680,0.00325950,0.00425152,0.00477115,0.00566870,0.00566870,0.00609385,0.00505459,0.00448772,0.00273987,0.00132270,-0.00009448,-0.00136993,-0.00141717,-0.00136993,-0.00004724,0.00099202,0.00255091,0.00382637,0.00415704,0.00481839,0.00410980,0.00406257,0.00292883,0.00269263,0.00151165,0.00151165,0.00094478,0.00080307,0.00066135,0.00070859,-0.00014172,0.00028343,-0.00146441,-0.00132270,-0.00264539,-0.00283435,-0.00325950,-0.00330674,-0.00311778,-0.00325950,-0.00259815,-0.00311778,-0.00217300,-0.00273987,-0.00222024,-0.00255091,-0.00207852,-0.00212576,-0.00170061,-0.00184233,-0.00203128,-0.00179509,-0.00292883,-0.00255091,-0.00340122,-0.00321226,-0.00292883,-0.00278711,-0.00240920,-0.00212576,-0.00222024,-0.00212576,-0.00269263,-0.00297607,-0.00387361,-0.00462944,-0.00519630,-0.00637728,-0.00590489,-0.00680244,-0.00566870,-0.00562146,-0.00462944,-0.00359017,-0.00302330,-0.00179509,-0.00160613,-0.00113374,-0.00108650,-0.00070859,-0.00037791,0.00080307,0.00141717,0.00307054,0.00406257,0.00481839,0.00491287,0.00420428,0.00259815,0.00108650,-0.00141717,-0.00297607,-0.00462944,-0.00496011,-0.00477115,-0.00401533,-0.00231472,-0.00099202,0.00028343,0.00170061,0.00184233,0.00245644,0.00179509,0.00184233,0.00136993,0.00151165,0.00146441,0.00179509,0.00226748,0.00193680,0.00259815,0.00132270,0.00170061,0.00037791,-0.00014172,-0.00051963,-0.00132270,-0.00080307,-0.00089754,-0.00009448,0.00018896,0.00103926,0.00047239,0.00080307,-0.00085030,-0.00099202,-0.00236196,-0.00198404,-0.00207852,-0.00118098,-0.00033067,0.00070859,0.00118098,0.00188957,0.00198404,0.00297607,0.00288159,0.00410980,0.00406257,0.00458220,0.00500735,0.00467667,0.00472391,0.00401533,0.00359017,0.00264539,0.00179509,0.00108650,0.00023620,-0.00009448,-0.00061411,-0.00089754,-0.00132270,-0.00127546,-0.00179509,-0.00165337,-0.00188957,-0.00188957,-0.00198404,-0.00170061,-0.00212576,-0.00160613,-0.00226748,-0.00170061,-0.00240920,-0.00151165,-0.00170061,-0.00033067,-0.00014172,0.00070859,0.00061411,0.00028343,-0.00037791,-0.00136993,-0.00236196,-0.00297607,-0.00335398,-0.00368465,-0.00349570,-0.00340122,-0.00283435,-0.00226748,-0.00122822,-0.00108650,0.00051963,0.00051963,0.00188957,0.00222024,0.00283435,0.00307054,0.00283435,0.00212576,0.00160613,0.00023620,-0.00051963,-0.00151165,-0.00259815,-0.00302330,-0.00377913,-0.00349570,-0.00325950,-0.00240920,-0.00132270,-0.00061411,0.00028343,0.00066135,0.00103926,0.00132270,0.00170061,0.00170061,0.00146441,0.00170061,0.00042515,0.00061411,-0.00089754,-0.00066135,-0.00151165,-0.00099202,-0.00089754,-0.00023620,0.00037791,0.00066135,0.00132270,0.00118098,0.00141717,0.00099202,-0.00023620,-0.00085030,-0.00297607,-0.00396809,-0.00557422,-0.00651900,-0.00699139,-0.00680244,-0.00604661,-0.00458220,-0.00335398,-0.00113374,-0.00051963,0.00061411,0.00066135,0.00004724,-0.00009448,-0.00146441,-0.00136993,-0.00217300,-0.00207852,-0.00212576,-0.00236196,-0.00222024,-0.00250367,-0.00259815,-0.00273987,-0.00283435,-0.00302330,-0.00311778,-0.00330674,-0.00325950,-0.00354294,-0.00325950,-0.00330674,-0.00302330,-0.00311778,-0.00236196,-0.00245644,-0.00118098,-0.00141717,-0.00051963,-0.00085030,-0.00085030,-0.00160613,-0.00207852,-0.00302330,-0.00278711,-0.00344846,-0.00264539,-0.00269263,-0.00212576,-0.00165337,-0.00151165,-0.00085030,-0.00108650,-0.00018896,-0.00085030,0.00000000,-0.00051963,-0.00009448,-0.00033067,0.00028343,0.00023620,0.00042515,0.00018896,0.00000000,-0.00094478,-0.00108650,-0.00226748,-0.00212576,-0.00212576,-0.00151165,-0.00103926,0.00009448,0.00028343,0.00151165,0.00170061,0.00255091,0.00278711,0.00311778,0.00321226,0.00283435,0.00226748,0.00155889,0.00061411,-0.00018896,-0.00132270,-0.00179509,-0.00297607,-0.00264539,-0.00335398,-0.00222024,-0.00203128,-0.00085030,-0.00014172,0.00056687,0.00122822,0.00170061,0.00151165,0.00136993,0.00113374,-0.00028343,-0.00066135,-0.00160613,-0.00212576,-0.00122822,-0.00151165,0.00033067,0.00037791,0.00151165,0.00118098,0.00103926,0.00014172,-0.00009448,-0.00141717,-0.00080307,-0.00165337,-0.00047239,-0.00023620,0.00056687,0.00103926,0.00136993,0.00127546,0.00061411,0.00014172,-0.00089754,-0.00160613,-0.00155889,-0.00217300,-0.00103926,-0.00080307,0.00075583,0.00141717,0.00212576,0.00283435,0.00264539,0.00325950,0.00288159,0.00321226,0.00330674,0.00359017,0.00321226,0.00359017,0.00250367,0.00236196,0.00212576,0.00108650,0.00217300,0.00160613,0.00255091,0.00278711,0.00288159,0.00259815,0.00198404,0.00132270,0.00004724,-0.00009448,-0.00132270,-0.00113374,-0.00179509,-0.00184233,-0.00184233,-0.00222024,-0.00188957,-0.00198404,-0.00174785,-0.00155889,-0.00146441,-0.00155889,-0.00132270,-0.00165337,-0.00122822,-0.00170061,-0.00146441,-0.00231472,-0.00259815,-0.00316502,-0.00349570,-0.00387361,-0.00425152,-0.00434600,-0.00491287,-0.00510183,-0.00604661,-0.00599937,-0.00680244,-0.00581041,-0.00618833,-0.00462944,-0.00448772,-0.00330674,-0.00316502,-0.00278711,-0.00349570,-0.00387361,-0.00448772,-0.00496011,-0.00514907,-0.00514907,-0.00557422,-0.00514907,-0.00547974,-0.00500735,-0.00496011,-0.00425152,-0.00401533,-0.00297607,-0.00236196,-0.00207852,-0.00136993,-0.00174785,-0.00193680,-0.00174785,-0.00288159,-0.00184233,-0.00240920,-0.00160613,-0.00132270,-0.00094478,-0.00028343,-0.00004724,0.00056687,0.00014172,0.00056687,-0.00061411,-0.00070859,-0.00198404,-0.00264539,-0.00368465,-0.00396809,-0.00458220,-0.00401533,-0.00420428,-0.00321226,-0.00273987,-0.00212576,-0.00155889,-0.00179509,-0.00141717,-0.00207852,-0.00146441,-0.00198404,-0.00094478,-0.00085030,0.00000000,0.00051963,0.00085030,0.00118098,0.00089754,0.00108650,0.00056687,0.00080307,0.00080307,0.00056687,0.00099202,-0.00009448,0.00047239,-0.00061411,0.00009448,-0.00037791,0.00094478,0.00099202,0.00226748,0.00255091,0.00264539,0.00297607,0.00245644,0.00226748,0.00226748,0.00203128,0.00245644,0.00273987,0.00325950,0.00344846,0.00340122,0.00344846,0.00231472,0.00226748,0.00094478,0.00051963,0.00004724,-0.00056687,-0.00085030,-0.00146441,-0.00240920,-0.00311778,-0.00425152,-0.00505459,-0.00529078,-0.00562146,-0.00425152,-0.00368465,-0.00198404,-0.00122822,-0.00051963,-0.00075583,-0.00108650,-0.00212576,-0.00231472,-0.00240920,-0.00113374,0.00018896,0.00236196,0.00410980,0.00538526,0.00633004,0.00562146,0.00529078,0.00335398,0.00236196,0.00051963,-0.00028343,-0.00089754,-0.00051963,0.00051963,0.00207852,0.00387361,0.00566870,0.00670796,0.00760550,0.00722759,0.00713311,0.00571594,0.00462944,0.00307054,0.00174785,0.00080307,-0.00023620,-0.00080307,-0.00094478,-0.00188957,-0.00122822,-0.00193680,-0.00122822,-0.00085030,-0.00023620,0.00028343,0.00132270,0.00127546,0.00179509,0.00188957,0.00207852,0.00217300,0.00240920,0.00198404,0.00212576,0.00136993,0.00160613,0.00056687,0.00118098,0.00023620,0.00089754,-0.00018896,0.00085030,-0.00037791,0.00051963,-0.00023620,0.00037791,-0.00014172,0.00094478,0.00056687,0.00198404,0.00207852,0.00302330,0.00316502,0.00344846,0.00325950,0.00245644,0.00240920,0.00066135,0.00047239,-0.00113374,-0.00155889,-0.00302330,-0.00344846,-0.00462944,-0.00477115,-0.00562146,-0.00547974,-0.00571594,-0.00547974,-0.00524354,-0.00477115,-0.00392085,-0.00302330,-0.00198404,-0.00122822,-0.00014172,-0.00009448,0.00056687,0.00037791,0.00009448,-0.00009448,-0.00061411,-0.00099202,-0.00108650,-0.00108650,-0.00103926,-0.00080307,-0.00061411,-0.00075583,-0.00094478,-0.00146441,-0.00222024,-0.00240920,-0.00278711,-0.00212576,-0.00160613,-0.00042515,0.00066135,0.00146441,0.00283435,0.00288159,0.00410980,0.00377913,0.00392085,0.00377913,0.00278711,0.00269263,0.00203128,0.00179509,0.00207852,0.00198404,0.00264539,0.00292883,0.00302330,0.00307054,0.00273987,0.00226748,0.00165337,0.00146441,0.00099202,0.00122822,0.00113374,0.00075583,0.00103926,0.00018896,0.00028343,-0.00042515,-0.00037791,-0.00103926,-0.00113374,-0.00179509,-0.00226748,-0.00240920,-0.00231472,-0.00250367,-0.00132270,-0.00184233,-0.00066135,-0.00141717,-0.00108650,-0.00165337,-0.00179509,-0.00217300,-0.00184233,-0.00226748,-0.00122822,-0.00136993,-0.00028343,-0.00033067,0.00042515,-0.00014172,-0.00009448,-0.00042515,-0.00089754,-0.00056687,-0.00037791,0.00061411,0.00165337,0.00250367,0.00330674,0.00368465,0.00359017,0.00321226,0.00203128,0.00108650,-0.00037791,-0.00118098,-0.00174785,-0.00113374,-0.00051963,0.00141717,0.00273987,0.00425152,0.00543250,0.00491287,0.00510183,0.00359017,0.00273987,0.00193680,0.00113374,0.00165337,0.00165337,0.00297607,0.00377913,0.00472391,0.00585765,0.00566870,0.00656624,0.00524354,0.00529078,0.00363741,0.00297607,0.00160613,0.00066135,0.00028343,-0.00033067,0.00023620,0.00028343,0.00122822,0.00217300,0.00297607,0.00377913,0.00396809,0.00278711,0.00217300,-0.00051963,-0.00146441,-0.00302330,-0.00297607,-0.00250367,-0.00217300,-0.00170061,-0.00174785,-0.00174785,-0.00203128,-0.00170061,-0.00226748,-0.00226748,-0.00292883,-0.00396809,-0.00429876,-0.00547974,-0.00491287,-0.00510183,-0.00425152,-0.00401533,-0.00392085,-0.00382637,-0.00377913,-0.00359017,-0.00368465,-0.00311778,-0.00363741,-0.00288159,-0.00354294,-0.00325950,-0.00335398,-0.00311778,-0.00217300,-0.00132270,0.00023620,0.00113374,0.00245644,0.00302330,0.00321226,0.00311778,0.00255091,0.00174785,0.00136993,0.00023620,-0.00004724,-0.00033067,-0.00094478,-0.00042515,-0.00099202,-0.00037791,-0.00051963,-0.00023620,-0.00009448,0.00037791,0.00066135,0.00113374,0.00103926,0.00155889,0.00122822,0.00122822,0.00066135,-0.00018896,-0.00089754,-0.00212576,-0.00297607,-0.00392085,-0.00467667,-0.00538526,-0.00557422,-0.00552698,-0.00529078,-0.00425152,-0.00401533,-0.00278711,-0.00273987,-0.00160613,-0.00179509,-0.00075583,-0.00033067,0.00014172,0.00141717,0.00155889,0.00250367,0.00321226,0.00359017,0.00467667,0.00467667,0.00581041,0.00543250,0.00614109,0.00562146,0.00533802,0.00529078,0.00425152,0.00429876,0.00292883,0.00316502,0.00203128,0.00236196,0.00203128,0.00226748,0.00278711,0.00321226,0.00429876,0.00453496,0.00547974,0.00533802,0.00519630,0.00491287,0.00373189,0.00297607,0.00146441,0.00066135,0.00009448,-0.00028343,0.00037791,0.00009448,0.00122822,0.00075583,0.00103926,0.00047239,-0.00009448,-0.00047239,-0.00075583,-0.00061411,-0.00023620,0.00028343,0.00122822,0.00179509,0.00273987,0.00273987,0.00316502,0.00240920,0.00198404,0.00080307,-0.00028343,-0.00113374,-0.00212576,-0.00283435,-0.00307054,-0.00373189,-0.00325950,-0.00396809,-0.00316502,-0.00434600,-0.00368465,-0.00453496,-0.00462944,-0.00467667,-0.00472391,-0.00472391,-0.00406257,-0.00429876,-0.00420428,-0.00387361,-0.00410980,-0.00311778,-0.00321226,-0.00217300,-0.00212576,-0.00113374,-0.00146441,-0.00118098,-0.00155889,-0.00155889,-0.00122822,-0.00136993,0.00018896,0.00033067,0.00250367,0.00316502,0.00415704,0.00505459,0.00458220,0.00429876,0.00368465,0.00212576,0.00184233,0.00023620,-0.00042515,-0.00108650,-0.00236196,-0.00273987,-0.00344846,-0.00354294,-0.00344846,-0.00269263,-0.00236196,-0.00146441,-0.00075583,-0.00056687,-0.00028343,0.00000000,-0.00061411,-0.00009448,-0.00075583,-0.00080307,-0.00146441,-0.00212576,-0.00292883,-0.00429876,-0.00505459,-0.00628280,-0.00675520,-0.00651900,-0.00642452,-0.00472391,-0.00387361,-0.00245644,-0.00136993,-0.00075583,-0.00028343,-0.00009448,0.00018896,0.00047239,0.00118098,0.00184233,0.00226748,0.00316502,0.00250367,0.00264539,0.00127546,0.00028343,-0.00113374,-0.00193680,-0.00278711,-0.00269263,-0.00269263,-0.00231472,-0.00160613,-0.00160613,-0.00118098,-0.00136993,-0.00136993,-0.00118098,-0.00132270,-0.00066135,-0.00118098,0.00000000,-0.00056687,0.00042515,0.00018896,-0.00004724,-0.00004724,-0.00089754,-0.00146441,-0.00179509,-0.00236196,-0.00203128,-0.00160613,-0.00118098,-0.00033067,0.00000000,0.00000000,0.00009448,-0.00061411,-0.00099202,-0.00188957,-0.00236196,-0.00259815,-0.00273987,-0.00259815,-0.00264539,-0.00212576,-0.00198404,-0.00127546,-0.00028343,0.00000000,0.00160613,0.00179509,0.00288159,0.00335398,0.00344846,0.00340122,0.00316502,0.00160613,0.00127546,-0.00056687,-0.00066135,-0.00203128,-0.00151165,-0.00198404,-0.00122822,-0.00136993,-0.00127546,-0.00155889,-0.00136993,-0.00184233,-0.00080307,-0.00108650,0.00028343,0.00023620,0.00080307,0.00033067,0.00000000,-0.00127546,-0.00136993,-0.00174785,-0.00028343,0.00066135,0.00311778,0.00425152,0.00519630,0.00547974,0.00406257,0.00368465,0.00283435,0.00264539,0.00330674,0.00359017,0.00410980,0.00458220,0.00349570,0.00340122,0.00132270,0.00080307,-0.00089754,-0.00141717,-0.00245644,-0.00226748,-0.00255091,-0.00255091,-0.00212576,-0.00250367,-0.00151165,-0.00212576,-0.00118098,-0.00122822,-0.00042515,0.00014172,0.00094478,0.00160613,0.00217300,0.00278711,0.00292883,0.00269263,0.00231472,0.00089754,-0.00056687,-0.00203128,-0.00420428,-0.00477115,-0.00623557,-0.00571594,-0.00599937,-0.00425152,-0.00377913,-0.00170061,-0.00118098,0.00004724,0.00000000,-0.00037791,-0.00080307,-0.00179509,-0.00231472,-0.00236196,-0.00297607,-0.00240920,-0.00231472,-0.00226748,-0.00165337,-0.00170061,-0.00103926,-0.00094478,-0.00028343,0.00009448,0.00070859,0.00165337,0.00170061,0.00264539,0.00188957,0.00188957,0.00103926,0.00023620,-0.00033067,-0.00094478,-0.00165337,-0.00160613,-0.00250367,-0.00231472,-0.00273987,-0.00273987,-0.00259815,-0.00245644,-0.00236196,-0.00174785,-0.00174785,-0.00075583,-0.00089754,0.00004724,0.00018896,0.00085030,0.00099202,0.00155889,0.00184233,0.00250367,0.00292883,0.00325950,0.00368465,0.00330674,0.00269263,0.00188957,-0.00004724,-0.00118098,-0.00330674,-0.00425152,-0.00590489,-0.00637728,-0.00708587,-0.00666072,-0.00581041,-0.00453496,-0.00250367,-0.00160613,0.00047239,0.00066135,0.00103926,0.00099202,-0.00028343,-0.00075583,-0.00212576,-0.00302330,-0.00382637,-0.00396809,-0.00444048,-0.00377913,-0.00359017,-0.00231472,-0.00155889,-0.00028343,0.00108650,0.00184233,0.00335398,0.00269263,0.00349570,0.00179509,0.00222024,0.00047239,0.00066135,0.00004724,0.00028343,0.00042515,0.00037791,0.00056687,-0.00004724,-0.00037791,-0.00080307,-0.00141717,-0.00132270,-0.00146441,-0.00099202,-0.00075583,-0.00023620,0.00009448,-0.00028343,0.00009448,-0.00094478,-0.00075583,-0.00075583,-0.00009448,0.00113374,0.00245644,0.00387361,0.00477115,0.00500735,0.00448772,0.00330674,0.00188957,0.00018896,-0.00113374,-0.00222024,-0.00264539,-0.00307054,-0.00259815,-0.00231472,-0.00122822,-0.00037791,0.00103926,0.00222024,0.00354294,0.00467667,0.00448772,0.00533802,0.00387361,0.00429876,0.00269263,0.00226748,0.00165337,0.00113374,0.00132270,0.00103926,0.00132270,0.00118098,0.00179509,0.00155889,0.00193680,0.00179509,0.00146441,0.00127546,0.00051963,-0.00009448,-0.00033067,-0.00132270,-0.00099202,-0.00146441,-0.00136993,-0.00141717,-0.00174785,-0.00222024,-0.00240920,-0.00316502,-0.00278711,-0.00321226,-0.00217300,-0.00226748,-0.00155889,-0.00141717,-0.00155889,-0.00155889,-0.00184233,-0.00160613,-0.00127546,-0.00066135,-0.00014172,0.00099202,0.00151165,0.00240920,0.00273987,0.00255091,0.00330674,0.00226748,0.00273987,0.00188957,0.00226748,0.00193680,0.00231472,0.00250367,0.00273987,0.00283435,0.00302330,0.00283435,0.00255091,0.00283435,0.00203128,0.00231472,0.00231472,0.00207852,0.00250367,0.00250367,0.00222024,0.00212576,0.00108650,0.00028343,-0.00056687,-0.00136993,-0.00141717,-0.00141717,-0.00042515,0.00042515,0.00136993,0.00231472,0.00264539,0.00250367,0.00240920,0.00127546,0.00122822,0.00009448,0.00066135,0.00004724,0.00080307,0.00056687,0.00066135,0.00056687,0.00000000,-0.00018896,-0.00089754,-0.00099202,-0.00089754,-0.00085030,0.00014172,0.00028343,0.00094478,0.00146441,0.00066135,0.00094478,-0.00070859,-0.00080307,-0.00203128,-0.00226748,-0.00212576,-0.00226748,-0.00165337,-0.00188957,-0.00203128,-0.00259815,-0.00406257,-0.00448772,-0.00585765,-0.00595213,-0.00547974,-0.00571594,-0.00439324,-0.00458220,-0.00434600,-0.00467667,-0.00510183,-0.00543250,-0.00581041,-0.00571594,-0.00547974,-0.00500735,-0.00467667,-0.00396809,-0.00401533,-0.00330674,-0.00354294,-0.00278711,-0.00269263,-0.00151165,-0.00127546,-0.00004724,-0.00009448,0.00070859,0.00014172,0.00028343,-0.00061411,-0.00099202,-0.00136993,-0.00203128,-0.00136993,-0.00155889,-0.00018896,0.00033067,0.00179509,0.00212576,0.00264539,0.00273987,0.00207852,0.00184233,0.00094478,0.00061411,0.00018896,0.00009448,-0.00023620,-0.00009448,-0.00023620,0.00028343,0.00028343,0.00099202,0.00118098,0.00226748,0.00222024,0.00255091,0.00236196,0.00207852,0.00174785,0.00188957,0.00155889,0.00207852,0.00222024,0.00174785,0.00151165,0.00099202,0.00004724,0.00051963,0.00004724,0.00085030,0.00198404,0.00273987,0.00429876,0.00514907,0.00633004,0.00684967,0.00751102,0.00670796,0.00656624,0.00552698,0.00415704,0.00344846,0.00170061,0.00089754,-0.00023620,-0.00103926,-0.00155889,-0.00179509,-0.00179509,-0.00188957,-0.00141717,-0.00188957,-0.00127546,-0.00198404,-0.00184233,-0.00222024,-0.00240920,-0.00236196,-0.00236196,-0.00198404,-0.00122822,-0.00066135,0.00009448,0.00080307,0.00066135,0.00113374,0.00014172,0.00014172,-0.00108650,-0.00103926,-0.00207852,-0.00132270,-0.00222024,-0.00051963,-0.00141717,0.00028343,-0.00009448,0.00047239,0.00037791,-0.00023620,-0.00085030,-0.00136993,-0.00236196,-0.00222024,-0.00259815,-0.00255091,-0.00240920,-0.00240920,-0.00255091,-0.00273987,-0.00307054,-0.00321226,-0.00288159,-0.00273987,-0.00141717,-0.00122822,0.00070859,0.00037791,0.00136993,0.00066135,-0.00037791,-0.00051963,-0.00236196,-0.00222024,-0.00311778,-0.00273987,-0.00217300,-0.00160613,-0.00042515,0.00014172,0.00051963,0.00023620,-0.00037791,-0.00132270,-0.00174785,-0.00193680,-0.00198404,-0.00103926,-0.00080307,0.00009448,-0.00004724,0.00033067,-0.00042515,-0.00051963,-0.00089754,-0.00132270,-0.00099202,-0.00118098,-0.00061411,-0.00051963,0.00018896,0.00000000,0.00018896,0.00014172,-0.00023620,0.00014172,-0.00047239,0.00004724,-0.00023620,0.00009448,0.00037791,0.00047239,0.00085030,0.00089754,0.00061411,0.00056687,-0.00018896,-0.00070859,-0.00099202,-0.00136993,-0.00113374,-0.00075583,-0.00089754,0.00004724,-0.00089754,-0.00037791,-0.00146441,-0.00193680,-0.00222024,-0.00278711,-0.00288159,-0.00245644,-0.00264539,-0.00188957,-0.00155889,-0.00089754,-0.00033067,0.00042515,0.00061411,0.00136993,0.00146441,0.00155889,0.00151165,0.00160613,0.00198404,0.00226748,0.00283435,0.00297607,0.00410980,0.00392085,0.00481839,0.00467667,0.00486563,0.00486563,0.00444048,0.00439324,0.00410980,0.00368465,0.00377913,0.00278711,0.00250367,0.00155889,0.00070859,-0.00004724,-0.00047239,-0.00094478,-0.00127546,-0.00127546,-0.00184233,-0.00188957,-0.00226748,-0.00245644,-0.00245644,-0.00236196,-0.00250367,-0.00203128,-0.00212576,-0.00174785,-0.00136993,-0.00122822,-0.00113374,-0.00099202,-0.00151165,-0.00203128,-0.00231472,-0.00359017,-0.00387361,-0.00519630,-0.00524354,-0.00590489,-0.00547974,-0.00500735,-0.00359017,-0.00236196,-0.00066135,0.00061411,0.00136993,0.00250367,0.00165337,0.00250367,0.00094478,0.00155889,0.00014172,0.00047239,-0.00051963,-0.00080307,-0.00165337,-0.00217300,-0.00288159,-0.00292883,-0.00283435,-0.00273987,-0.00193680,-0.00184233,-0.00118098,-0.00089754,-0.00085030,-0.00051963,-0.00037791,-0.00023620,0.00004724,0.00023620,0.00061411,0.00075583,0.00089754,0.00103926]" --greatHall :: [Double] --greatHall = read "[0.02286254,0.00491261,-0.02035900,-0.01662730,0.01237600,0.02555503,0.00136986,-0.02876712,-0.02083137,0.01738309,0.03419934,0.00420406,-0.03240435,-0.02239017,0.02390175,0.04029287,-0.00051960,-0.04553614,-0.02838923,0.03169580,0.05111006,-0.00429854,-0.05772319,-0.02697213,0.05403873,0.06759565,-0.02102031,-0.09244214,-0.02843647,0.09881908,0.09220595,-0.08233349,-0.16433632,0.12900331,0.66905999,0.90000000,0.36608408,-0.71705243,-1.54411904,-1.44870099,-0.54926783,0.38039679,0.68360888,0.39853566,0.07595654,0.11204535,0.37642891,0.48119981,0.28767123,0.03070383,-0.01709967,0.12489372,0.21247048,0.11596599,-0.04043458,-0.06192726,0.05281058,0.13193198,0.06088805,-0.07926311,-0.13259329,-0.07846009,-0.03793103,-0.10817194,-0.23363250,-0.28653755,-0.23131790,-0.15465281,-0.14799244,-0.19433160,-0.21757204,-0.18379783,-0.14303259,-0.14038734,-0.15592820,-0.14284365,-0.10486538,-0.10198394,-0.16102976,-0.23419934,-0.24067076,-0.17397260,-0.10203118,-0.09069438,-0.12649976,-0.14213510,-0.10529051,-0.04785073,-0.02120926,-0.02564950,-0.02220123,0.01856401,0.06934341,0.09206424,0.07283892,0.04341049,0.03249882,0.04185168,0.04893718,0.04194615,0.03056212,0.02810581,0.03934813,0.05394426,0.06693434,0.07581483,0.08200283,0.08313651,0.07642891,0.06466698,0.05082664,0.04095418,0.03816722,0.04534719,0.06088805,0.07085498,0.06428909,0.03575815,0.00184223,-0.01733585,-0.01445442,0.00160605,0.01554086,0.02040624,0.02215399,0.02158715,0.01922532,0.01133680,0.00505432,0.00670761,0.01870572,0.02886160,0.03008975,0.02390175,0.02102031,0.02824752,0.03764761,0.03731696,0.02328767,0.00396788,-0.00576287,-0.00340104,0.00958904,0.02201228,0.03320737,0.04506377,0.05937648,0.07345300,0.07945205,0.07378366,0.05847898,0.04444969,0.03476618,0.03249882,0.02942844,0.02470477,0.02300425,0.02820028,0.03972603,0.04803968,0.04615021,0.03712801,0.03145961,0.03160132,0.03396316,0.02801134,0.01771375,0.01119509,0.01832782,0.03311290,0.04307983,0.04388285,0.03859235,0.03911195,0.04492206,0.04888994,0.04378838,0.03438829,0.02867265,0.03386868,0.04307983,0.04893718,0.04813415,0.04355220,0.04378838,0.04591403,0.04794521,0.04303259,0.03490789,0.02923949,0.03316013,0.04615021,0.05673122,0.05762872,0.04520548,0.03216816,0.02919225,0.03826169,0.04685876,0.04416627,0.02957015,0.01846953,0.01799717,0.02475201,0.02347662,0.01039206,-0.00373170,-0.00415683,0.00779405,0.01804440,0.01336797,-0.00047237,-0.00892773,-0.00278696,0.00987246,0.01643836,0.01374587,0.00708550,0.00217289,-0.00420406,-0.01336797,-0.02210675,-0.02092584,-0.01034483,-0.00118092,-0.00127539,-0.01048654,-0.01889466,-0.02305149,-0.02588569,-0.02706660,-0.01884743,-0.00099197,0.00892773,-0.01081719,-0.04657534,-0.04393009,0.04926783,0.20949457,0.32848370,0.29282003,0.08875768,-0.16750118,-0.32224846,-0.30670761,-0.18034955,-0.05994332,-0.00954180,-0.00765234,0.00349551,0.04359943,0.08564006,0.09744922,0.08072744,0.05743977,0.03944261,0.01114785,-0.03386868,-0.08138876,-0.09829948,-0.07520076,-0.03873406,-0.02796410,-0.06249410,-0.12125650,-0.16986301,-0.18096363,-0.15517241,-0.10628248,-0.05947095,-0.02735002,-0.02168162,-0.03311290,-0.05276334,-0.06490316,-0.07123288,-0.07137459,-0.07449221,-0.07477563,-0.07057156,-0.05838451,-0.03958432,-0.01662730,0.00973075,0.03396316,0.04770902,0.04459140,0.02749173,0.00973075,0.00255078,0.00533774,0.01166745,0.01336797,0.01700520,0.02664147,0.04558337,0.06466698,0.07534247,0.07453944,0.06740671,0.05810109,0.04959849,0.04071800,0.03259329,0.02564950,0.02253188,0.02281530,0.02508266,0.02980633,0.03320737,0.03457723,0.03391592,0.03094001,0.02990080,0.02890883,0.02853094,0.02890883,0.03108172,0.03585262,0.03849787,0.03656117,0.02876712,0.02158715,0.01724138,0.01539915,0.01204535,0.00595182,0.00212565,0.00340104,0.00836089,0.01048654,0.00722721,0.00486538,0.00751063,0.01757204,0.02456306,0.02824752,0.02853094,0.03240435,0.03410487,0.02484648,-0.00094473,-0.02621634,-0.02966462,0.00155881,0.04922060,0.07912140,0.06632026,0.01525744,-0.04619745,-0.08989136,-0.10462919,-0.09489844,-0.06632026,-0.01993387,0.03887577,0.09546528,0.12413793,0.11294284,0.07137459,0.02853094,0.00481814,0.00141710,-0.00113368,-0.01388758,-0.02763344,-0.02390175,0.00505432,0.04119036,0.05503070,0.03514407,-0.00344828,-0.03367974,-0.03873406,-0.02697213,-0.01308455,-0.00344828,0.00864431,0.02890883,0.05219650,0.06310817,0.05696741,0.04133207,0.03131790,0.03221540,0.03637222,0.03448276,0.02668871,0.02220123,0.02810581,0.03712801,0.04071800,0.02990080,0.01624941,0.00779405,0.01020312,0.01549362,0.01374587,0.00595182,-0.00004724,0.00481814,0.01870572,0.03264053,0.03939537,0.03972603,0.04048181,0.04222957,0.04307983,0.03547473,0.02092584,0.00547945,-0.00321209,-0.00245631]" reverb :: DSPEffect reverb = convolve ([1.0] ++ replicate 500 0.0 ++ [0.8] ++ replicate 500 0.0 ++ [0.6] ++ replicate 500 0.0 ++ [0.1]) -- here we mix it all together and apply the effects notesToSignal :: (Oscillator -> [Note] -> SampledSignal) -> [[Note]] -> SampledSignal notesToSignal playNotes tracks = audio where -- specify the instruments of each track -- try the following instruments with the mario.mid file instrs = cycle [piano_good] audioTracks = zipWith playNotes' instrs tracks audioNoEffects = mixTracks audioTracks [0.8, 0.7] --audio = audioNoEffects -- To add effects, replace the line above by the line at the end of this comment and change the list off effects to your own effects. -- Note that the effects are applied from right to left, ie. the rightmost effect is applied first. audio = addEffects [reverb] audioNoEffects -- If you want to apply an effect only to parts of the signal, you can use the function applyEffectToInterval, as shown below. -- Thereby the first argument specifies the interval to which the effect should be applied in seconds. -- audio = applyEffectToInterval (2, 6) audioNoEffects distortion {-TTEW-}