criterion-1.1.0.0/0000755000000000000000000000000012505102676012037 5ustar0000000000000000criterion-1.1.0.0/changelog.md0000644000000000000000000000037112505102676014311 0ustar00000000000000001.1.0.0 * 1.0.2.0 * Bump lower bound on optparse-applicative to 0.11 to handle yet more annoying API churn. 1.0.1.0 * Added a lower bound of 0.10 on the optparse-applicative dependency, as there were major API changes between 0.9 and 0.10. criterion-1.1.0.0/criterion.cabal0000644000000000000000000000674312505102676015033 0ustar0000000000000000name: criterion version: 1.1.0.0 synopsis: Robust, reliable performance measurement and analysis license: BSD3 license-file: LICENSE author: Bryan O'Sullivan maintainer: Bryan O'Sullivan copyright: 2009-2014 Bryan O'Sullivan category: Development, Performance, Testing, Benchmarking homepage: http://www.serpentine.com/criterion bug-reports: https://github.com/bos/criterion/issues build-type: Simple cabal-version: >= 1.8 extra-source-files: README.markdown changelog.md examples/*.cabal examples/*.hs examples/*.html js-src/flot-0.8.3.zip js-src/jquery-2.1.1.js data-files: templates/*.css templates/*.tpl templates/js/jquery-2.1.1.min.js templates/js/jquery.criterion.js templates/js/jquery.flot-0.8.3.min.js description: This library provides a powerful but simple way to measure software performance. It provides both a framework for executing and analysing benchmarks and a set of driver functions that makes it easy to build and run benchmarks, and to analyse their results. . The fastest way to get started is to read the , followed by the documentation and examples in the "Criterion.Main" module. . For examples of the kinds of reports that criterion generates, see . library exposed-modules: Criterion Criterion.Analysis Criterion.IO Criterion.IO.Printf Criterion.Internal Criterion.Main Criterion.Main.Options Criterion.Measurement Criterion.Monad Criterion.Report Criterion.Types other-modules: Criterion.Monad.Internal c-sources: cbits/cycles.c if os(darwin) c-sources: cbits/time-osx.c else { if os(windows) c-sources: cbits/time-windows.c else c-sources: cbits/time-posix.c } other-modules: Paths_criterion build-depends: aeson >= 0.8, ansi-wl-pprint >= 0.6.7.2, base >= 4.5 && < 5, binary >= 0.5.1.0, bytestring >= 0.9 && < 1.0, cassava >= 0.3.0.0, containers, deepseq >= 1.1.0.0, directory, filepath, Glob >= 0.7.2, hastache >= 0.6.0, mtl >= 2, mwc-random >= 0.8.0.3, optparse-applicative >= 0.11, parsec >= 3.1.0, statistics >= 0.13.2.1, text >= 0.11, time, transformers, transformers-compat >= 0.4, vector >= 0.7.1, vector-algorithms >= 0.4 if impl(ghc < 7.6) build-depends: ghc-prim ghc-options: -O2 -Wall -funbox-strict-fields if impl(ghc >= 6.8) ghc-options: -fwarn-tabs executable criterion buildable: False hs-source-dirs: app main-is: App.hs ghc-options: -Wall -threaded -rtsopts build-depends: base, criterion test-suite sanity type: exitcode-stdio-1.0 hs-source-dirs: tests main-is: Sanity.hs ghc-options: -O2 -Wall -rtsopts build-depends: HUnit, base, bytestring, criterion, test-framework, test-framework-hunit test-suite tests type: exitcode-stdio-1.0 hs-source-dirs: tests main-is: Tests.hs other-modules: Properties ghc-options: -Wall -threaded -O0 -rtsopts build-depends: QuickCheck >= 2.4, base, criterion, statistics, test-framework >= 0.4, test-framework-quickcheck2 >= 0.2, vector source-repository head type: git location: https://github.com/bos/criterion.git criterion-1.1.0.0/Criterion.hs0000644000000000000000000000313412505102676014332 0ustar0000000000000000{-# LANGUAGE RecordWildCards #-} -- | -- Module : Criterion -- Copyright : (c) 2009-2014 Bryan O'Sullivan -- -- License : BSD-style -- Maintainer : bos@serpentine.com -- Stability : experimental -- Portability : GHC -- -- Core benchmarking code. module Criterion ( -- * Benchmarkable code Benchmarkable -- * Creating a benchmark suite , Benchmark , env , bench , bgroup -- ** Running a benchmark , nf , whnf , nfIO , whnfIO -- * For interactive use , benchmark , benchmarkWith , benchmark' , benchmarkWith' ) where import Control.Monad (void) import Criterion.IO.Printf (note) import Criterion.Internal (runAndAnalyseOne) import Criterion.Main.Options (defaultConfig) import Criterion.Measurement (initializeTime) import Criterion.Monad (withConfig) import Criterion.Types -- | Run a benchmark interactively, and analyse its performance. benchmark :: Benchmarkable -> IO () benchmark bm = void $ benchmark' bm -- | Run a benchmark interactively, analyse its performance, and -- return the analysis. benchmark' :: Benchmarkable -> IO Report benchmark' = benchmarkWith' defaultConfig -- | Run a benchmark interactively, and analyse its performance. benchmarkWith :: Config -> Benchmarkable -> IO () benchmarkWith cfg bm = void $ benchmarkWith' cfg bm -- | Run a benchmark interactively, analyse its performance, and -- return the analysis. benchmarkWith' :: Config -> Benchmarkable -> IO Report benchmarkWith' cfg bm = do initializeTime withConfig cfg $ do _ <- note "benchmarking...\n" runAndAnalyseOne 0 "function" bm criterion-1.1.0.0/LICENSE0000644000000000000000000000265212505102676013051 0ustar0000000000000000Copyright (c) 2009, 2010 Bryan O'Sullivan All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: * Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. * Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. Some files in templates/js have their own copyright and license, please refer to the corresponding sources in js-src/. criterion-1.1.0.0/README.markdown0000644000000000000000000000224112505102676014537 0ustar0000000000000000# Criterion: robust, reliable performance measurement This package provides the Criterion module, a Haskell library for measuring and analysing software performance. To get started, read the online tutorial, and take a look at the programs in the examples directory. # Building and installing To build and install criterion, just run cabal install criterion # Get involved! Please report bugs via the [github issue tracker](https://github.com/bos/criterion/issues). Master [github repository](https://github.com/bos/criterion): * `git clone https://github.com/bos/criterion.git` There's also a [Mercurial mirror](https://bitbucket.org/bos/criterion): * `hg clone https://bitbucket.org/bos/criterion` (You can create and contribute changes using either Mercurial or git.) # Authors This library is written and maintained by Bryan O'Sullivan, . criterion-1.1.0.0/Setup.lhs0000644000000000000000000000011412505102676013643 0ustar0000000000000000#!/usr/bin/env runhaskell > import Distribution.Simple > main = defaultMain criterion-1.1.0.0/app/0000755000000000000000000000000012505102676012617 5ustar0000000000000000criterion-1.1.0.0/app/App.hs0000644000000000000000000000007612505102676013676 0ustar0000000000000000module Main (main) where main :: IO () main = do return () criterion-1.1.0.0/cbits/0000755000000000000000000000000012505102676013143 5ustar0000000000000000criterion-1.1.0.0/cbits/cycles.c0000644000000000000000000000026512505102676014574 0ustar0000000000000000#include "Rts.h" StgWord64 criterion_rdtsc(void) { StgWord32 hi, lo; __asm__ __volatile__ ("rdtsc" : "=a"(lo), "=d"(hi)); return ((StgWord64) lo) | (((StgWord64) hi)<<32); } criterion-1.1.0.0/cbits/time-osx.c0000644000000000000000000000161012505102676015052 0ustar0000000000000000#include #include static mach_timebase_info_data_t timebase_info; static double timebase_recip; void criterion_inittime(void) { if (timebase_recip == 0) { mach_timebase_info(&timebase_info); timebase_recip = (timebase_info.denom / timebase_info.numer) / 1e9; } } double criterion_gettime(void) { return mach_absolute_time() * timebase_recip; } static double to_double(time_value_t time) { return time.seconds + time.microseconds / 1e6; } double criterion_getcputime(void) { struct task_thread_times_info thread_info_data; mach_msg_type_number_t thread_info_count = TASK_THREAD_TIMES_INFO_COUNT; kern_return_t kr = task_info(mach_task_self(), TASK_THREAD_TIMES_INFO, (task_info_t) &thread_info_data, &thread_info_count); return (to_double(thread_info_data.user_time) + to_double(thread_info_data.system_time)); } criterion-1.1.0.0/cbits/time-posix.c0000644000000000000000000000054412505102676015410 0ustar0000000000000000#include void criterion_inittime(void) { } double criterion_gettime(void) { struct timespec ts; clock_gettime(CLOCK_MONOTONIC, &ts); return ts.tv_sec + ts.tv_nsec * 1e-9; } double criterion_getcputime(void) { struct timespec ts; clock_gettime(CLOCK_PROCESS_CPUTIME_ID, &ts); return ts.tv_sec + ts.tv_nsec * 1e-9; } criterion-1.1.0.0/cbits/time-windows.c0000644000000000000000000000327312505102676015742 0ustar0000000000000000/* * Windows has the most amazingly cretinous time measurement APIs you * can possibly imagine. * * Our first possibility is GetSystemTimeAsFileTime, which updates at * roughly 60Hz, and is hence worthless - we'd have to run a * computation for tens or hundreds of seconds to get a trustworthy * number. * * Alternatively, we can use QueryPerformanceCounter, which has * undefined behaviour under almost all interesting circumstances * (e.g. multicore systems, CPU frequency changes). But at least it * increments reasonably often. */ #include #if 0 void criterion_inittime(void) { } double criterion_gettime(void) { FILETIME ft; ULARGE_INTEGER li; GetSystemTimeAsFileTime(&ft); li.LowPart = ft.dwLowDateTime; li.HighPart = ft.dwHighDateTime; return (li.QuadPart - 130000000000000000ull) * 1e-7; } #else static double freq_recip; static LARGE_INTEGER firstClock; void criterion_inittime(void) { LARGE_INTEGER freq; if (freq_recip == 0) { QueryPerformanceFrequency(&freq); QueryPerformanceCounter(&firstClock); freq_recip = 1.0 / freq.QuadPart; } } double criterion_gettime(void) { LARGE_INTEGER li; QueryPerformanceCounter(&li); return ((double) (li.QuadPart - firstClock.QuadPart)) * freq_recip; } #endif static ULONGLONG to_quad_100ns(FILETIME ft) { ULARGE_INTEGER li; li.LowPart = ft.dwLowDateTime; li.HighPart = ft.dwHighDateTime; return li.QuadPart; } double criterion_getcputime(void) { FILETIME creation, exit, kernel, user; ULONGLONG time; GetProcessTimes(GetCurrentProcess(), &creation, &exit, &kernel, &user); time = to_quad_100ns(user) + to_quad_100ns(kernel); return time / 1e7; } criterion-1.1.0.0/Criterion/0000755000000000000000000000000012505102676013775 5ustar0000000000000000criterion-1.1.0.0/Criterion/Analysis.hs0000644000000000000000000002270412505102676016121 0ustar0000000000000000{-# LANGUAGE BangPatterns, DeriveDataTypeable, RecordWildCards #-} -- | -- Module : Criterion.Analysis -- Copyright : (c) 2009-2014 Bryan O'Sullivan -- -- License : BSD-style -- Maintainer : bos@serpentine.com -- Stability : experimental -- Portability : GHC -- -- Analysis code for benchmarks. module Criterion.Analysis ( Outliers(..) , OutlierEffect(..) , OutlierVariance(..) , SampleAnalysis(..) , analyseSample , scale , analyseMean , countOutliers , classifyOutliers , noteOutliers , outlierVariance , resolveAccessors , validateAccessors , regress ) where import Control.Arrow (second) import Control.Monad (unless, when) import Control.Monad.Reader (ask) import Control.Monad.Trans import Control.Monad.Trans.Except import Criterion.IO.Printf (note, prolix) import Criterion.Measurement (secs, threshold) import Criterion.Monad (Criterion, getGen, getOverhead) import Criterion.Types import Data.Int (Int64) import Data.Maybe (fromJust) import Data.Monoid (Monoid(..)) import Statistics.Function (sort) import Statistics.Quantile (weightedAvg) import Statistics.Regression (bootstrapRegress, olsRegress) import Statistics.Resampling (resample) import Statistics.Sample (mean) import Statistics.Sample.KernelDensity (kde) import Statistics.Types (Estimator(..), Sample) import System.Random.MWC (GenIO) import qualified Data.List as List import qualified Data.Map as Map import qualified Data.Vector as V import qualified Data.Vector.Generic as G import qualified Data.Vector.Unboxed as U import qualified Statistics.Resampling.Bootstrap as B -- | Classify outliers in a data set, using the boxplot technique. classifyOutliers :: Sample -> Outliers classifyOutliers sa = U.foldl' ((. outlier) . mappend) mempty ssa where outlier e = Outliers { samplesSeen = 1 , lowSevere = if e <= loS && e < hiM then 1 else 0 , lowMild = if e > loS && e <= loM then 1 else 0 , highMild = if e >= hiM && e < hiS then 1 else 0 , highSevere = if e >= hiS && e > loM then 1 else 0 } !loS = q1 - (iqr * 3) !loM = q1 - (iqr * 1.5) !hiM = q3 + (iqr * 1.5) !hiS = q3 + (iqr * 3) q1 = weightedAvg 1 4 ssa q3 = weightedAvg 3 4 ssa ssa = sort sa iqr = q3 - q1 -- | Compute the extent to which outliers in the sample data affect -- the sample mean and standard deviation. outlierVariance :: B.Estimate -- ^ Bootstrap estimate of sample mean. -> B.Estimate -- ^ Bootstrap estimate of sample -- standard deviation. -> Double -- ^ Number of original iterations. -> OutlierVariance outlierVariance µ σ a = OutlierVariance effect desc varOutMin where ( effect, desc ) | varOutMin < 0.01 = (Unaffected, "no") | varOutMin < 0.1 = (Slight, "slight") | varOutMin < 0.5 = (Moderate, "moderate") | otherwise = (Severe, "severe") varOutMin = (minBy varOut 1 (minBy cMax 0 µgMin)) / σb2 varOut c = (ac / a) * (σb2 - ac * σg2) where ac = a - c σb = B.estPoint σ µa = B.estPoint µ / a µgMin = µa / 2 σg = min (µgMin / 4) (σb / sqrt a) σg2 = σg * σg σb2 = σb * σb minBy f q r = min (f q) (f r) cMax x = fromIntegral (floor (-2 * k0 / (k1 + sqrt det)) :: Int) where k1 = σb2 - a * σg2 + ad k0 = -a * ad ad = a * d d = k * k where k = µa - x det = k1 * k1 - 4 * σg2 * k0 -- | Count the total number of outliers in a sample. countOutliers :: Outliers -> Int64 countOutliers (Outliers _ a b c d) = a + b + c + d {-# INLINE countOutliers #-} -- | Display the mean of a 'Sample', and characterise the outliers -- present in the sample. analyseMean :: Sample -> Int -- ^ Number of iterations used to -- compute the sample. -> Criterion Double analyseMean a iters = do let µ = mean a _ <- note "mean is %s (%d iterations)\n" (secs µ) iters noteOutliers . classifyOutliers $ a return µ -- | Multiply the 'Estimate's in an analysis by the given value, using -- 'B.scale'. scale :: Double -- ^ Value to multiply by. -> SampleAnalysis -> SampleAnalysis scale f s@SampleAnalysis{..} = s { anMean = B.scale f anMean , anStdDev = B.scale f anStdDev } -- | Perform an analysis of a measurement. analyseSample :: Int -- ^ Experiment number. -> String -- ^ Experiment name. -> V.Vector Measured -- ^ Sample data. -> ExceptT String Criterion Report analyseSample i name meas = do Config{..} <- ask overhead <- lift getOverhead let ests = [Mean,StdDev] -- The use of filter here throws away very-low-quality -- measurements when bootstrapping the mean and standard -- deviations. Without this, the numbers look nonsensical when -- very brief actions are measured. stime = measure (measTime . rescale) . G.filter ((>= threshold) . measTime) . G.map fixTime . G.tail $ meas fixTime m = m { measTime = measTime m - overhead / 2 } n = G.length meas s = G.length stime _ <- lift $ prolix "bootstrapping with %d of %d samples (%d%%)\n" s n ((s * 100) `quot` n) gen <- lift getGen rs <- mapM (\(ps,r) -> regress gen ps r meas) $ ((["iters"],"time"):regressions) resamps <- liftIO $ resample gen ests resamples stime let [estMean,estStdDev] = B.bootstrapBCA confInterval stime ests resamps ov = outlierVariance estMean estStdDev (fromIntegral n) an = SampleAnalysis { anRegress = rs , anOverhead = overhead , anMean = estMean , anStdDev = estStdDev , anOutlierVar = ov } return Report { reportNumber = i , reportName = name , reportKeys = measureKeys , reportMeasured = meas , reportAnalysis = an , reportOutliers = classifyOutliers stime , reportKDEs = [uncurry (KDE "time") (kde 128 stime)] } -- | Regress the given predictors against the responder. -- -- Errors may be returned under various circumstances, such as invalid -- names or lack of needed data. -- -- See 'olsRegress' for details of the regression performed. regress :: GenIO -> [String] -- ^ Predictor names. -> String -- ^ Responder name. -> V.Vector Measured -> ExceptT String Criterion Regression regress gen predNames respName meas = do when (G.null meas) $ throwE "no measurements" accs <- ExceptT . return $ validateAccessors predNames respName let unmeasured = [n | (n, Nothing) <- map (second ($ G.head meas)) accs] unless (null unmeasured) $ throwE $ "no data available for " ++ renderNames unmeasured let (r:ps) = map ((`measure` meas) . (fromJust .) . snd) accs Config{..} <- ask (coeffs,r2) <- liftIO $ bootstrapRegress gen resamples confInterval olsRegress ps r return Regression { regResponder = respName , regCoeffs = Map.fromList (zip (predNames ++ ["y"]) (G.toList coeffs)) , regRSquare = r2 } singleton :: [a] -> Bool singleton [_] = True singleton _ = False -- | Given a list of accessor names (see 'measureKeys'), return either -- a mapping from accessor name to function or an error message if -- any names are wrong. resolveAccessors :: [String] -> Either String [(String, Measured -> Maybe Double)] resolveAccessors names = case unresolved of [] -> Right [(n, a) | (n, Just (a,_)) <- accessors] _ -> Left $ "unknown metric " ++ renderNames unresolved where unresolved = [n | (n, Nothing) <- accessors] accessors = flip map names $ \n -> (n, Map.lookup n measureAccessors) -- | Given predictor and responder names, do some basic validation, -- then hand back the relevant accessors. validateAccessors :: [String] -- ^ Predictor names. -> String -- ^ Responder name. -> Either String [(String, Measured -> Maybe Double)] validateAccessors predNames respName = do when (null predNames) $ Left "no predictors specified" let names = respName:predNames dups = map head . filter (not . singleton) . List.group . List.sort $ names unless (null dups) $ Left $ "duplicated metric " ++ renderNames dups resolveAccessors names renderNames :: [String] -> String renderNames = List.intercalate ", " . map show -- | Display a report of the 'Outliers' present in a 'Sample'. noteOutliers :: Outliers -> Criterion () noteOutliers o = do let frac n = (100::Double) * fromIntegral n / fromIntegral (samplesSeen o) check :: Int64 -> Double -> String -> Criterion () check k t d = when (frac k > t) $ note " %d (%.1g%%) %s\n" k (frac k) d outCount = countOutliers o when (outCount > 0) $ do _ <- note "found %d outliers among %d samples (%.1g%%)\n" outCount (samplesSeen o) (frac outCount) check (lowSevere o) 0 "low severe" check (lowMild o) 1 "low mild" check (highMild o) 1 "high mild" check (highSevere o) 0 "high severe" criterion-1.1.0.0/Criterion/Internal.hs0000644000000000000000000001624612505102676016116 0ustar0000000000000000{-# LANGUAGE BangPatterns, RecordWildCards #-} -- | -- Module : Criterion -- Copyright : (c) 2009-2014 Bryan O'Sullivan -- -- License : BSD-style -- Maintainer : bos@serpentine.com -- Stability : experimental -- Portability : GHC -- -- Core benchmarking code. module Criterion.Internal ( runAndAnalyse , runAndAnalyseOne , runNotAnalyse ) where import Control.DeepSeq (rnf) import Control.Exception (evaluate) import Control.Monad (foldM, forM_, void, when) import Control.Monad.Reader (ask, asks) import Control.Monad.Trans (liftIO) import Control.Monad.Trans.Except import Data.Binary (encode) import Data.Int (Int64) import qualified Data.ByteString.Lazy as L import Criterion.Analysis (analyseSample, noteOutliers) import Criterion.IO (header, hGetReports) import Criterion.IO.Printf (note, printError, prolix, writeCsv) import Criterion.Measurement (runBenchmark, secs) import Criterion.Monad (Criterion) import Criterion.Report (report) import Criterion.Types hiding (measure) import qualified Data.Map as Map import Statistics.Resampling.Bootstrap (Estimate(..)) import System.Directory (getTemporaryDirectory, removeFile) import System.IO (IOMode(..), SeekMode(..), hClose, hSeek, openBinaryFile, openBinaryTempFile) import Text.Printf (printf) -- | Run a single benchmark and analyse its performance. runAndAnalyseOne :: Int -> String -> Benchmarkable -> Criterion Report runAndAnalyseOne i desc bm = do Config{..} <- ask (meas,timeTaken) <- liftIO $ runBenchmark bm timeLimit when (timeTaken > timeLimit * 1.25) . void $ prolix "measurement took %s\n" (secs timeTaken) _ <- prolix "analysing with %d resamples\n" resamples erp <- runExceptT $ analyseSample i desc meas case erp of Left err -> printError "*** Error: %s\n" err Right rpt@Report{..} -> do let SampleAnalysis{..} = reportAnalysis OutlierVariance{..} = anOutlierVar wibble = case ovEffect of Unaffected -> "unaffected" :: String Slight -> "slightly inflated" Moderate -> "moderately inflated" Severe -> "severely inflated" (builtin, others) = splitAt 1 anRegress let r2 n = printf "%.3f R\178" n forM_ builtin $ \Regression{..} -> case Map.lookup "iters" regCoeffs of Nothing -> return () Just t -> bs secs "time" t >> bs r2 "" regRSquare bs secs "mean" anMean bs secs "std dev" anStdDev forM_ others $ \Regression{..} -> do _ <- bs r2 (regResponder ++ ":") regRSquare forM_ (Map.toList regCoeffs) $ \(prd,val) -> bs (printf "%.3g") (" " ++ prd) val writeCsv (desc, estPoint anMean, estLowerBound anMean, estUpperBound anMean, estPoint anStdDev, estLowerBound anStdDev, estUpperBound anStdDev) when (verbosity == Verbose || (ovEffect > Slight && verbosity > Quiet)) $ do when (verbosity == Verbose) $ noteOutliers reportOutliers _ <- note "variance introduced by outliers: %d%% (%s)\n" (round (ovFraction * 100) :: Int) wibble return () _ <- note "\n" return rpt where bs :: (Double -> String) -> String -> Estimate -> Criterion () bs f metric Estimate{..} = note "%-20s %-10s (%s .. %s%s)\n" metric (f estPoint) (f estLowerBound) (f estUpperBound) (if estConfidenceLevel == 0.95 then "" else printf ", ci %.3f" estConfidenceLevel) -- | Determine whether an Environment benchmark should be run. shouldRunEnv :: (String -> Bool) -> String -> (s -> Benchmark) -> Bool shouldRunEnv p pfx mkbench = any (p . addPrefix pfx) . benchNames . mkbench $ undefined -- | Run, and analyse, one or more benchmarks. runAndAnalyse :: (String -> Bool) -- ^ A predicate that chooses -- whether to run a benchmark by its -- name. -> Benchmark -> Criterion () runAndAnalyse p bs' = do mbRawFile <- asks rawDataFile (rawFile, handle) <- liftIO $ case mbRawFile of Nothing -> do tmpDir <- getTemporaryDirectory openBinaryTempFile tmpDir "criterion.dat" Just file -> do handle <- openBinaryFile file ReadWriteMode return (file, handle) liftIO $ L.hPut handle header let go !k (pfx, Environment mkenv mkbench) | shouldRunEnv p pfx mkbench = do e <- liftIO $ do ee <- mkenv evaluate (rnf ee) return ee go k (pfx, mkbench e) | otherwise = return (k :: Int) go !k (pfx, Benchmark desc b) | p desc' = do _ <- note "benchmarking %s\n" desc' rpt <- runAndAnalyseOne k desc' b liftIO $ L.hPut handle (encode rpt) return $! k + 1 | otherwise = return (k :: Int) where desc' = addPrefix pfx desc go !k (pfx, BenchGroup desc bs) = foldM go k [(addPrefix pfx desc, b) | b <- bs] _ <- go 0 ("", bs') rpts <- (either fail return =<<) . liftIO $ do hSeek handle AbsoluteSeek 0 rs <- hGetReports handle hClose handle case mbRawFile of Just _ -> return rs _ -> removeFile rawFile >> return rs report rpts junit rpts -- | Run a benchmark without analysing its performance. runNotAnalyse :: Int64 -- ^ Number of loop iterations to run. -> (String -> Bool) -- ^ A predicate that chooses -- whether to run a benchmark by its -- name. -> Benchmark -> Criterion () runNotAnalyse iters p bs' = goQuickly "" bs' where goQuickly :: String -> Benchmark -> Criterion () goQuickly pfx (Environment mkenv mkbench) | shouldRunEnv p pfx mkbench = do e <- liftIO mkenv goQuickly pfx (mkbench e) | otherwise = return () goQuickly pfx (Benchmark desc b) | p desc' = do _ <- note "benchmarking %s\n" desc' runOne b | otherwise = return () where desc' = addPrefix pfx desc goQuickly pfx (BenchGroup desc bs) = mapM_ (goQuickly (addPrefix pfx desc)) bs runOne (Benchmarkable run) = liftIO (run iters) -- | Write summary JUnit file (if applicable) junit :: [Report] -> Criterion () junit rs = do junitOpt <- asks junitFile case junitOpt of Just fn -> liftIO $ writeFile fn msg Nothing -> return () where msg = "\n" ++ printf "\n" (length rs) ++ concatMap single rs ++ "\n" single Report{..} = printf " \n" (attrEsc reportName) (estPoint $ anMean $ reportAnalysis) attrEsc = concatMap esc where esc '\'' = "'" esc '"' = """ esc '<' = "<" esc '>' = ">" esc '&' = "&" esc c = [c] criterion-1.1.0.0/Criterion/IO.hs0000644000000000000000000000466612505102676014654 0ustar0000000000000000{-# LANGUAGE CPP, OverloadedStrings #-} -- | -- Module : Criterion.IO -- Copyright : (c) 2009-2014 Bryan O'Sullivan -- -- License : BSD-style -- Maintainer : bos@serpentine.com -- Stability : experimental -- Portability : GHC -- -- Input and output actions. module Criterion.IO ( header , hGetReports , hPutReports , readReports , writeReports ) where import Criterion.Types (Report(..)) import Data.Binary (Binary(..), encode) #if MIN_VERSION_binary(0, 6, 3) import Data.Binary.Get (runGetOrFail) #else import Data.Binary.Get (runGetState) #endif import Data.Binary.Put (putByteString, putWord16be, runPut) import Data.ByteString.Char8 () import Data.Version (Version(..)) import Paths_criterion (version) import System.IO (Handle, IOMode(..), withFile) import qualified Data.ByteString.Lazy as L -- | The header identifies a criterion data file. This contains -- version information; there is no expectation of cross-version -- compatibility. header :: L.ByteString header = runPut $ do putByteString "criterio" mapM_ (putWord16be . fromIntegral) (versionBranch version) -- | Read all reports from the given 'Handle'. hGetReports :: Handle -> IO (Either String [Report]) hGetReports handle = do bs <- L.hGet handle (fromIntegral (L.length header)) if bs == header then Right `fmap` readAll handle else return $ Left "unexpected header" -- | Write reports to the given 'Handle'. hPutReports :: Handle -> [Report] -> IO () hPutReports handle rs = do L.hPut handle header mapM_ (L.hPut handle . encode) rs -- | Read all reports from the given file. readReports :: FilePath -> IO (Either String [Report]) readReports path = withFile path ReadMode hGetReports -- | Write reports to the given file. writeReports :: FilePath -> [Report] -> IO () writeReports path rs = withFile path WriteMode (flip hPutReports rs) #if MIN_VERSION_binary(0, 6, 3) readAll :: Binary a => Handle -> IO [a] readAll handle = do let go bs | L.null bs = return [] | otherwise = case runGetOrFail get bs of Left (_, _, err) -> fail err Right (bs', _, a) -> (a:) `fmap` go bs' go =<< L.hGetContents handle #else readAll :: Binary a => Handle -> IO [a] readAll handle = do let go i bs | L.null bs = return [] | otherwise = let (a, bs', i') = runGetState get bs i in (a:) `fmap` go i' bs' go 0 =<< L.hGetContents handle #endif criterion-1.1.0.0/Criterion/Main.hs0000644000000000000000000001621412505102676015221 0ustar0000000000000000-- | -- Module : Criterion.Main -- Copyright : (c) 2009-2014 Bryan O'Sullivan -- -- License : BSD-style -- Maintainer : bos@serpentine.com -- Stability : experimental -- Portability : GHC -- -- Wrappers for compiling and running benchmarks quickly and easily. -- See 'defaultMain' below for an example. module Criterion.Main ( -- * How to write benchmarks -- $bench -- ** Benchmarking IO actions -- $io -- ** Benchmarking pure code -- $pure -- ** Fully evaluating a result -- $rnf -- * Types Benchmarkable , Benchmark -- * Creating a benchmark suite , env , bench , bgroup -- ** Running a benchmark , nf , whnf , nfIO , whnfIO -- * Turning a suite of benchmarks into a program , defaultMain , defaultMainWith , defaultConfig -- * Other useful code , makeMatcher ) where import Control.Monad (unless) import Control.Monad.Trans (liftIO) import Criterion.IO.Printf (printError, writeCsv) import Criterion.Internal (runAndAnalyse, runNotAnalyse) import Criterion.Main.Options (MatchType(..), Mode(..), defaultConfig, describe, versionInfo) import Criterion.Measurement (initializeTime) import Criterion.Monad (withConfig) import Criterion.Types import Data.List (isPrefixOf, sort, stripPrefix) import Data.Maybe (fromMaybe) import Options.Applicative (execParser) import System.Environment (getProgName) import System.Exit (ExitCode(..), exitWith) import System.FilePath.Glob -- | An entry point that can be used as a @main@ function. -- -- > import Criterion.Main -- > -- > fib :: Int -> Int -- > fib 0 = 0 -- > fib 1 = 1 -- > fib n = fib (n-1) + fib (n-2) -- > -- > main = defaultMain [ -- > bgroup "fib" [ bench "10" $ whnf fib 10 -- > , bench "35" $ whnf fib 35 -- > , bench "37" $ whnf fib 37 -- > ] -- > ] defaultMain :: [Benchmark] -> IO () defaultMain = defaultMainWith defaultConfig -- | Create a function that can tell if a name given on the command -- line matches a benchmark. makeMatcher :: MatchType -> [String] -- ^ Command line arguments. -> Either String (String -> Bool) makeMatcher matchKind args = case matchKind of Prefix -> Right $ \b -> null args || any (`isPrefixOf` b) args Glob -> let compOptions = compDefault { errorRecovery = False } in case mapM (tryCompileWith compOptions) args of Left errMsg -> Left . fromMaybe errMsg . stripPrefix "compile :: " $ errMsg Right ps -> Right $ \b -> null ps || any (`match` b) ps selectBenches :: MatchType -> [String] -> Benchmark -> IO (String -> Bool) selectBenches matchType benches bsgroup = do toRun <- either parseError return . makeMatcher matchType $ benches unless (null benches || any toRun (benchNames bsgroup)) $ parseError "none of the specified names matches a benchmark" return toRun -- | An entry point that can be used as a @main@ function, with -- configurable defaults. -- -- Example: -- -- > import Criterion.Main.Options -- > import Criterion.Main -- > -- > myConfig = defaultConfig { -- > -- Do not GC between runs. -- > forceGC = False -- > } -- > -- > main = defaultMainWith myConfig [ -- > bench "fib 30" $ whnf fib 30 -- > ] -- -- If you save the above example as @\"Fib.hs\"@, you should be able -- to compile it as follows: -- -- > ghc -O --make Fib -- -- Run @\"Fib --help\"@ on the command line to get a list of command -- line options. defaultMainWith :: Config -> [Benchmark] -> IO () defaultMainWith defCfg bs = do wat <- execParser (describe defCfg) let bsgroup = BenchGroup "" bs case wat of List -> mapM_ putStrLn . sort . concatMap benchNames $ bs Version -> putStrLn versionInfo OnlyRun iters matchType benches -> do shouldRun <- selectBenches matchType benches bsgroup withConfig defaultConfig $ runNotAnalyse iters shouldRun bsgroup Run cfg matchType benches -> do shouldRun <- selectBenches matchType benches bsgroup withConfig cfg $ do writeCsv ("Name","Mean","MeanLB","MeanUB","Stddev","StddevLB", "StddevUB") liftIO initializeTime runAndAnalyse shouldRun bsgroup -- | Display an error message from a command line parsing failure, and -- exit. parseError :: String -> IO a parseError msg = do _ <- printError "Error: %s\n" msg _ <- printError "Run \"%s --help\" for usage information\n" =<< getProgName exitWith (ExitFailure 64) -- $bench -- -- The 'Benchmarkable' type is a container for code that can be -- benchmarked. The value inside must run a benchmark the given -- number of times. We are most interested in benchmarking two -- things: -- -- * 'IO' actions. Any 'IO' action can be benchmarked directly. -- -- * Pure functions. GHC optimises aggressively when compiling with -- @-O@, so it is easy to write innocent-looking benchmark code that -- doesn't measure the performance of a pure function at all. We -- work around this by benchmarking both a function and its final -- argument together. -- $io -- -- Any 'IO' action can be benchmarked easily if its type resembles -- this: -- -- @ -- 'IO' a -- @ -- $pure -- -- Because GHC optimises aggressively when compiling with @-O@, it is -- potentially easy to write innocent-looking benchmark code that will -- only be evaluated once, for which all but the first iteration of -- the timing loop will be timing the cost of doing nothing. -- -- To work around this, we provide two functions for benchmarking pure -- code. -- -- The first will cause results to be fully evaluated to normal form -- (NF): -- -- @ -- 'nf' :: 'NFData' b => (a -> b) -> a -> 'Benchmarkable' -- @ -- -- The second will cause results to be evaluated to weak head normal -- form (the Haskell default): -- -- @ -- 'whnf' :: (a -> b) -> a -> 'Benchmarkable' -- @ -- -- As both of these types suggest, when you want to benchmark a -- function, you must supply two values: -- -- * The first element is the function, saturated with all but its -- last argument. -- -- * The second element is the last argument to the function. -- -- Here is an example that makes the use of these functions clearer. -- Suppose we want to benchmark the following function: -- -- @ -- firstN :: Int -> [Int] -- firstN k = take k [(0::Int)..] -- @ -- -- So in the easy case, we construct a benchmark as follows: -- -- @ -- 'nf' firstN 1000 -- @ -- $rnf -- -- The 'whnf' harness for evaluating a pure function only evaluates -- the result to weak head normal form (WHNF). If you need the result -- evaluated all the way to normal form, use the 'nf' function to -- force its complete evaluation. -- -- Using the @firstN@ example from earlier, to naive eyes it might -- /appear/ that the following code ought to benchmark the production -- of the first 1000 list elements: -- -- @ -- 'whnf' firstN 1000 -- @ -- -- Since we are using 'whnf', in this case the result will only be -- forced until it reaches WHNF, so what this would /actually/ -- benchmark is merely how long it takes to produce the first list -- element! criterion-1.1.0.0/Criterion/Measurement.hs0000644000000000000000000001562112505102676016623 0ustar0000000000000000{-# LANGUAGE BangPatterns, CPP, ForeignFunctionInterface, ScopedTypeVariables #-} -- | -- Module : Criterion.Measurement -- Copyright : (c) 2009-2014 Bryan O'Sullivan -- -- License : BSD-style -- Maintainer : bos@serpentine.com -- Stability : experimental -- Portability : GHC -- -- Benchmark measurement code. module Criterion.Measurement ( initializeTime , getTime , getCPUTime , getCycles , getGCStats , secs , measure , runBenchmark , measured , applyGCStats , threshold ) where import Criterion.Types (Benchmarkable(..), Measured(..)) import Data.Int (Int64) import Data.List (unfoldr) import Data.Word (Word64) import GHC.Stats (GCStats(..)) import System.Mem (performGC) import Text.Printf (printf) import qualified Control.Exception as Exc import qualified Data.Vector as V import qualified GHC.Stats as Stats -- | Try to get GC statistics, bearing in mind that the GHC runtime -- will throw an exception if statistics collection was not enabled -- using \"@+RTS -T@\". getGCStats :: IO (Maybe GCStats) getGCStats = (Just `fmap` Stats.getGCStats) `Exc.catch` \(_::Exc.SomeException) -> return Nothing -- | Measure the execution of a benchmark a given number of times. measure :: Benchmarkable -- ^ Operation to benchmark. -> Int64 -- ^ Number of iterations. -> IO (Measured, Double) measure (Benchmarkable run) iters = do startStats <- getGCStats startTime <- getTime startCpuTime <- getCPUTime startCycles <- getCycles run iters endTime <- getTime endCpuTime <- getCPUTime endCycles <- getCycles endStats <- getGCStats let !m = applyGCStats endStats startStats $ measured { measTime = max 0 (endTime - startTime) , measCpuTime = max 0 (endCpuTime - startCpuTime) , measCycles = max 0 (fromIntegral (endCycles - startCycles)) , measIters = iters } return (m, endTime) {-# INLINE measure #-} -- | The amount of time a benchmark must run for in order for us to -- have some trust in the raw measurement. -- -- We set this threshold so that we can generate enough data to later -- perform meaningful statistical analyses. -- -- The threshold is 30 milliseconds. One use of 'runBenchmark' must -- accumulate more than 300 milliseconds of total measurements above -- this threshold before it will finish. threshold :: Double threshold = 0.03 {-# INLINE threshold #-} -- | Run a single benchmark, and return measurements collected while -- executing it, along with the amount of time the measurement process -- took. runBenchmark :: Benchmarkable -> Double -- ^ Lower bound on how long the benchmarking process -- should take. In practice, this time limit may be -- exceeded in order to generate enough data to perform -- meaningful statistical analyses. -> IO (V.Vector Measured, Double) runBenchmark bm@(Benchmarkable run) timeLimit = do run 1 start <- performGC >> getTime let loop [] !_ !_ _ = error "unpossible!" loop (iters:niters) prev count acc = do (m, endTime) <- measure bm iters let overThresh = max 0 (measTime m - threshold) + prev -- We try to honour the time limit, but we also have more -- important constraints: -- -- We must generate enough data that bootstrapping won't -- simply crash. -- -- We need to generate enough measurements that have long -- spans of execution to outweigh the (rather high) cost of -- measurement. if endTime - start >= timeLimit && overThresh > threshold * 10 && count >= (4 :: Int) then do let !v = V.reverse (V.fromList acc) return (v, endTime - start) else loop niters overThresh (count+1) (m:acc) loop (squish (unfoldr series 1)) 0 0 [] -- Our series starts its growth very slowly when we begin at 1, so we -- eliminate repeated values. squish :: (Eq a) => [a] -> [a] squish ys = foldr go [] ys where go x xs = x : dropWhile (==x) xs series :: Double -> Maybe (Int64, Double) series k = Just (truncate l, l) where l = k * 1.05 -- | An empty structure. measured :: Measured measured = Measured { measTime = 0 , measCpuTime = 0 , measCycles = 0 , measIters = 0 , measAllocated = minBound , measNumGcs = minBound , measBytesCopied = minBound , measMutatorWallSeconds = bad , measMutatorCpuSeconds = bad , measGcWallSeconds = bad , measGcCpuSeconds = bad } where bad = -1/0 -- | Apply the difference between two sets of GC statistics to a -- measurement. applyGCStats :: Maybe GCStats -- ^ Statistics gathered at the __end__ of a run. -> Maybe GCStats -- ^ Statistics gathered at the __beginning__ of a run. -> Measured -- ^ Value to \"modify\". -> Measured applyGCStats (Just end) (Just start) m = m { measAllocated = diff bytesAllocated , measNumGcs = diff numGcs , measBytesCopied = diff bytesCopied , measMutatorWallSeconds = diff mutatorWallSeconds , measMutatorCpuSeconds = diff mutatorCpuSeconds , measGcWallSeconds = diff gcWallSeconds , measGcCpuSeconds = diff gcCpuSeconds } where diff f = f end - f start applyGCStats _ _ m = m -- | Convert a number of seconds to a string. The string will consist -- of four decimal places, followed by a short description of the time -- units. secs :: Double -> String secs k | k < 0 = '-' : secs (-k) | k >= 1 = k `with` "s" | k >= 1e-3 = (k*1e3) `with` "ms" #ifdef mingw32_HOST_OS | k >= 1e-6 = (k*1e6) `with` "us" #else | k >= 1e-6 = (k*1e6) `with` "μs" #endif | k >= 1e-9 = (k*1e9) `with` "ns" | k >= 1e-12 = (k*1e12) `with` "ps" | k >= 1e-15 = (k*1e15) `with` "fs" | k >= 1e-18 = (k*1e18) `with` "as" | otherwise = printf "%g s" k where with (t :: Double) (u :: String) | t >= 1e9 = printf "%.4g %s" t u | t >= 1e3 = printf "%.0f %s" t u | t >= 1e2 = printf "%.1f %s" t u | t >= 1e1 = printf "%.2f %s" t u | otherwise = printf "%.3f %s" t u -- | Set up time measurement. foreign import ccall unsafe "criterion_inittime" initializeTime :: IO () -- | Read the CPU cycle counter. foreign import ccall unsafe "criterion_rdtsc" getCycles :: IO Word64 -- | Return the current wallclock time, in seconds since some -- arbitrary time. -- -- You /must/ call 'initializeTime' once before calling this function! foreign import ccall unsafe "criterion_gettime" getTime :: IO Double -- | Return the amount of elapsed CPU time, combining user and kernel -- (system) time into a single measure. foreign import ccall unsafe "criterion_getcputime" getCPUTime :: IO Double criterion-1.1.0.0/Criterion/Monad.hs0000644000000000000000000000450112505102676015367 0ustar0000000000000000-- | -- Module : Criterion.Monad -- Copyright : (c) 2009 Neil Brown -- -- License : BSD-style -- Maintainer : bos@serpentine.com -- Stability : experimental -- Portability : GHC -- -- The environment in which most criterion code executes. module Criterion.Monad ( Criterion , withConfig , getGen , getOverhead ) where import Control.Monad.Reader (asks, runReaderT) import Control.Monad.Trans (liftIO) import Control.Monad (when) import Criterion.Measurement (measure, runBenchmark, secs) import Criterion.Monad.Internal (Criterion(..), Crit(..)) import Criterion.Types hiding (measure) import Data.IORef (IORef, newIORef, readIORef, writeIORef) import Statistics.Regression (olsRegress) import System.Random.MWC (GenIO, createSystemRandom) import qualified Data.Vector.Generic as G -- | Run a 'Criterion' action with the given 'Config'. withConfig :: Config -> Criterion a -> IO a withConfig cfg (Criterion act) = do g <- newIORef Nothing o <- newIORef Nothing runReaderT act (Crit cfg g o) -- | Return a random number generator, creating one if necessary. -- -- This is not currently thread-safe, but in a harmless way (we might -- call 'createSystemRandom' more than once if multiple threads race). getGen :: Criterion GenIO getGen = memoise gen createSystemRandom -- | Return an estimate of the measurement overhead. getOverhead :: Criterion Double getOverhead = do verbose <- asks ((== Verbose) . verbosity) memoise overhead $ do (meas,_) <- runBenchmark (whnfIO $ measure (whnfIO $ return ()) 1) 1 let metric get = G.convert . G.map get $ meas let o = G.head . fst $ olsRegress [metric (fromIntegral . measIters)] (metric measTime) when verbose . liftIO $ putStrLn $ "measurement overhead " ++ secs o return o -- | Memoise the result of an 'IO' action. -- -- This is not currently thread-safe, but hopefully in a harmless way. -- We might call the given action more than once if multiple threads -- race, so our caller's job is to write actions that can be run -- multiple times safely. memoise :: (Crit -> IORef (Maybe a)) -> IO a -> Criterion a memoise ref generate = do r <- Criterion $ asks ref liftIO $ do mv <- readIORef r case mv of Just rv -> return rv Nothing -> do rv <- generate writeIORef r (Just rv) return rv criterion-1.1.0.0/Criterion/Report.hs0000644000000000000000000002027212505102676015607 0ustar0000000000000000{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, OverloadedStrings, RecordWildCards, ScopedTypeVariables #-} -- | -- Module : Criterion.Report -- Copyright : (c) 2009-2014 Bryan O'Sullivan -- -- License : BSD-style -- Maintainer : bos@serpentine.com -- Stability : experimental -- Portability : GHC -- -- Reporting functions. module Criterion.Report ( formatReport , report , tidyTails -- * Rendering helper functions , TemplateException(..) , loadTemplate , includeFile , getTemplateDir , vector , vector2 ) where import Control.Exception (Exception, IOException, throwIO) import Control.Monad (mplus) import Control.Monad.IO.Class (MonadIO(liftIO)) import Control.Monad.Reader (ask) import Criterion.Monad (Criterion) import Criterion.Types import Data.Aeson.Encode (encodeToTextBuilder) import Data.Aeson.Types (toJSON) import Data.Data (Data, Typeable) import Data.Foldable (forM_) import GHC.Generics (Generic) import Paths_criterion (getDataFileName) import Statistics.Function (minMax) import System.Directory (doesFileExist) import System.FilePath ((), (<.>), isPathSeparator) import Text.Hastache (MuType(..)) import Text.Hastache.Context (mkGenericContext, mkStrContext, mkStrContextM) import qualified Control.Exception as E import qualified Data.Text as T import qualified Data.Text.IO as T import qualified Data.Text.Lazy as TL import qualified Data.Text.Lazy.Builder as TL import qualified Data.Text.Lazy.IO as TL import qualified Data.Vector.Generic as G import qualified Data.Vector.Unboxed as U import qualified Text.Hastache as H -- | Trim long flat tails from a KDE plot. tidyTails :: KDE -> KDE tidyTails KDE{..} = KDE { kdeType = kdeType , kdeValues = G.slice front winSize kdeValues , kdePDF = G.slice front winSize kdePDF } where tiny = uncurry subtract (minMax kdePDF) * 0.005 omitTiny = G.length . G.takeWhile ((<= tiny) . abs) front = omitTiny kdePDF back = omitTiny . G.reverse $ kdePDF winSize = G.length kdePDF - front - back -- | Return the path to the template and other files used for -- generating reports. getTemplateDir :: IO FilePath getTemplateDir = getDataFileName "templates" -- | Write out a series of 'Report' values to a single file, if -- configured to do so. report :: [Report] -> Criterion () report reports = do Config{..} <- ask forM_ reportFile $ \name -> liftIO $ do td <- getTemplateDir tpl <- loadTemplate [td,"."] template TL.writeFile name =<< formatReport reports tpl -- | Format a series of 'Report' values using the given Hastache -- template. formatReport :: [Report] -> T.Text -- ^ Hastache template. -> IO TL.Text formatReport reports template = do templates <- getTemplateDir let context "report" = return $ MuList $ map inner reports context "json" = return $ MuVariable (encode reports) context "include" = return $ MuLambdaM $ includeFile [templates] context _ = return $ MuNothing encode v = TL.toLazyText . encodeToTextBuilder . toJSON $ v inner r@Report{..} = mkStrContextM $ \nym -> case nym of "name" -> return . MuVariable . H.htmlEscape . TL.pack $ reportName "json" -> return $ MuVariable (encode r) "number" -> return $ MuVariable reportNumber "iters" -> return $ vector "x" iters "times" -> return $ vector "x" times "cycles" -> return $ vector "x" cycles "kdetimes" -> return $ vector "x" kdeValues "kdepdf" -> return $ vector "x" kdePDF "kde" -> return $ vector2 "time" "pdf" kdeValues kdePDF ('a':'n':_)-> mkGenericContext reportAnalysis $ H.encodeStr nym _ -> mkGenericContext reportOutliers $ H.encodeStr nym where [KDE{..}] = reportKDEs iters = measure measIters reportMeasured times = measure measTime reportMeasured cycles = measure measCycles reportMeasured config = H.defaultConfig { H.muEscapeFunc = H.emptyEscape , H.muTemplateFileDir = Just templates , H.muTemplateFileExt = Just ".tpl" } H.hastacheStr config template context -- | Render the elements of a vector. -- -- For example, given this piece of Haskell: -- -- @'mkStrContext' $ \\name -> -- case name of -- \"foo\" -> 'vector' \"x\" foo@ -- -- It will substitute each value in the vector for @x@ in the -- following Hastache template: -- -- > {{#foo}} -- > {{x}} -- > {{/foo}} vector :: (Monad m, G.Vector v a, H.MuVar a) => String -- ^ Name to use when substituting. -> v a -> MuType m {-# SPECIALIZE vector :: String -> U.Vector Double -> MuType IO #-} vector name v = MuList . map val . G.toList $ v where val i = mkStrContext $ \nym -> if nym == name then MuVariable i else MuNothing -- | Render the elements of two vectors. vector2 :: (Monad m, G.Vector v a, G.Vector v b, H.MuVar a, H.MuVar b) => String -- ^ Name for elements from the first vector. -> String -- ^ Name for elements from the second vector. -> v a -- ^ First vector. -> v b -- ^ Second vector. -> MuType m {-# SPECIALIZE vector2 :: String -> String -> U.Vector Double -> U.Vector Double -> MuType IO #-} vector2 name1 name2 v1 v2 = MuList $ zipWith val (G.toList v1) (G.toList v2) where val i j = mkStrContext $ \nym -> case undefined of _| nym == name1 -> MuVariable i | nym == name2 -> MuVariable j | otherwise -> MuNothing -- | Attempt to include the contents of a file based on a search path. -- Returns 'B.empty' if the search fails or the file could not be read. -- -- Intended for use with Hastache's 'MuLambdaM', for example: -- -- @context \"include\" = 'MuLambdaM' $ 'includeFile' ['templateDir']@ -- -- Hastache template expansion is /not/ performed within the included -- file. No attempt is made to ensure that the included file path is -- safe, i.e. that it does not refer to an unexpected file such as -- \"@/etc/passwd@\". includeFile :: (MonadIO m) => [FilePath] -- ^ Directories to search. -> T.Text -- ^ Name of the file to search for. -> m T.Text {-# SPECIALIZE includeFile :: [FilePath] -> T.Text -> IO T.Text #-} includeFile searchPath name = liftIO $ foldr go (return T.empty) searchPath where go dir next = do let path = dir H.decodeStr name T.readFile path `E.catch` \(_::IOException) -> next -- | A problem arose with a template. data TemplateException = TemplateNotFound FilePath -- ^ The template could not be found. deriving (Eq, Read, Show, Typeable, Data, Generic) instance Exception TemplateException -- | Load a Hastache template file. -- -- If the name is an absolute or relative path, the search path is -- /not/ used, and the name is treated as a literal path. -- -- This function throws a 'TemplateException' if the template could -- not be found, or an 'IOException' if no template could be loaded. loadTemplate :: [FilePath] -- ^ Search path. -> FilePath -- ^ Name of template file. -> IO T.Text loadTemplate paths name | any isPathSeparator name = T.readFile name | otherwise = go Nothing paths where go me (p:ps) = do let cur = p name <.> "tpl" x <- doesFileExist cur if x then T.readFile cur `E.catch` \e -> go (me `mplus` Just e) ps else go me ps go (Just e) _ = throwIO (e::IOException) go _ _ = throwIO . TemplateNotFound $ name criterion-1.1.0.0/Criterion/Types.hs0000644000000000000000000005760012505102676015445 0ustar0000000000000000{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, GADTs, RecordWildCards #-} {-# OPTIONS_GHC -funbox-strict-fields #-} -- | -- Module : Criterion.Types -- Copyright : (c) 2009-2014 Bryan O'Sullivan -- -- License : BSD-style -- Maintainer : bos@serpentine.com -- Stability : experimental -- Portability : GHC -- -- Types for benchmarking. -- -- The core type is 'Benchmarkable', which admits both pure functions -- and 'IO' actions. -- -- For a pure function of type @a -> b@, the benchmarking harness -- calls this function repeatedly, each time with a different 'Int64' -- argument (the number of times to run the function in a loop), and -- reduces the result the function returns to weak head normal form. -- -- For an action of type @IO a@, the benchmarking harness calls the -- action repeatedly, but does not reduce the result. module Criterion.Types ( -- * Configuration Config(..) , Verbosity(..) -- * Benchmark descriptions , Benchmarkable(..) , Benchmark(..) -- * Measurements , Measured(..) , fromInt , toInt , fromDouble , toDouble , measureAccessors , measureKeys , measure , rescale -- * Benchmark construction , env , bench , bgroup , addPrefix , benchNames -- ** Evaluation control , whnf , nf , nfIO , whnfIO -- * Result types , Outliers(..) , OutlierEffect(..) , OutlierVariance(..) , Regression(..) , KDE(..) , Report(..) , SampleAnalysis(..) ) where import Control.Applicative ((<$>), (<*>)) import Control.DeepSeq (NFData(rnf)) import Control.Exception (evaluate) import Data.Aeson (FromJSON(..), ToJSON(..)) import Data.Binary (Binary(..), putWord8, getWord8) import Data.Data (Data, Typeable) import Data.Int (Int64) import Data.Map (Map, fromList) import Data.Monoid (Monoid(..)) import GHC.Generics (Generic) import qualified Data.Vector as V import qualified Data.Vector.Unboxed as U import qualified Statistics.Resampling.Bootstrap as B -- | Control the amount of information displayed. data Verbosity = Quiet | Normal | Verbose deriving (Eq, Ord, Bounded, Enum, Read, Show, Typeable, Data, Generic) -- | Top-level benchmarking configuration. data Config = Config { confInterval :: Double -- ^ Confidence interval for bootstrap estimation (greater than -- 0, less than 1). , forceGC :: Bool -- ^ /Obsolete, unused/. This option used to force garbage -- collection between every benchmark run, but it no longer has -- an effect (we now unconditionally force garbage collection). -- This option remains solely for backwards API compatibility. , timeLimit :: Double -- ^ Number of seconds to run a single benchmark. (In practice, -- execution time will very slightly exceed this limit.) , resamples :: Int -- ^ Number of resamples to perform when bootstrapping. , regressions :: [([String], String)] -- ^ Regressions to perform. , rawDataFile :: Maybe FilePath -- ^ File to write binary measurement and analysis data to. If -- not specified, this will be a temporary file. , reportFile :: Maybe FilePath -- ^ File to write report output to, with template expanded. , csvFile :: Maybe FilePath -- ^ File to write CSV summary to. , junitFile :: Maybe FilePath -- ^ File to write JUnit-compatible XML results to. , verbosity :: Verbosity -- ^ Verbosity level to use when running and analysing -- benchmarks. , template :: FilePath -- ^ Template file to use if writing a report. } deriving (Eq, Read, Show, Typeable, Data, Generic) -- | A pure function or impure action that can be benchmarked. The -- 'Int64' parameter indicates the number of times to run the given -- function or action. newtype Benchmarkable = Benchmarkable (Int64 -> IO ()) -- | A collection of measurements made while benchmarking. -- -- Measurements related to garbage collection are tagged with __GC__. -- They will only be available if a benchmark is run with @\"+RTS -- -T\"@. -- -- __Packed storage.__ When GC statistics cannot be collected, GC -- values will be set to huge negative values. If a field is labeled -- with \"__GC__\" below, use 'fromInt' and 'fromDouble' to safely -- convert to \"real\" values. data Measured = Measured { measTime :: !Double -- ^ Total wall-clock time elapsed, in seconds. , measCpuTime :: !Double -- ^ Total CPU time elapsed, in seconds. Includes both user and -- kernel (system) time. , measCycles :: !Int64 -- ^ Cycles, in unspecified units that may be CPU cycles. (On -- i386 and x86_64, this is measured using the @rdtsc@ -- instruction.) , measIters :: !Int64 -- ^ Number of loop iterations measured. , measAllocated :: !Int64 -- ^ __(GC)__ Number of bytes allocated. Access using 'fromInt'. , measNumGcs :: !Int64 -- ^ __(GC)__ Number of garbage collections performed. Access -- using 'fromInt'. , measBytesCopied :: !Int64 -- ^ __(GC)__ Number of bytes copied during garbage collection. -- Access using 'fromInt'. , measMutatorWallSeconds :: !Double -- ^ __(GC)__ Wall-clock time spent doing real work -- (\"mutation\"), as distinct from garbage collection. Access -- using 'fromDouble'. , measMutatorCpuSeconds :: !Double -- ^ __(GC)__ CPU time spent doing real work (\"mutation\"), as -- distinct from garbage collection. Access using 'fromDouble'. , measGcWallSeconds :: !Double -- ^ __(GC)__ Wall-clock time spent doing garbage collection. -- Access using 'fromDouble'. , measGcCpuSeconds :: !Double -- ^ __(GC)__ CPU time spent doing garbage collection. Access -- using 'fromDouble'. } deriving (Eq, Read, Show, Typeable, Data, Generic) instance FromJSON Measured where parseJSON v = do (a,b,c,d,e,f,g,h,i,j,k) <- parseJSON v return $ Measured a b c d e f g h i j k instance ToJSON Measured where toJSON Measured{..} = toJSON (measTime, measCpuTime, measCycles, measIters, i measAllocated, i measNumGcs, i measBytesCopied, d measMutatorWallSeconds, d measMutatorCpuSeconds, d measGcWallSeconds, d measMutatorCpuSeconds) where i = fromInt; d = fromDouble instance NFData Measured where rnf Measured{} = () -- THIS MUST REFLECT THE ORDER OF FIELDS IN THE DATA TYPE. -- -- The ordering is used by Javascript code to pick out the correct -- index into the vector that represents a Measured value in that -- world. measureAccessors_ :: [(String, (Measured -> Maybe Double, String))] measureAccessors_ = [ ("time", (Just . measTime, "wall-clock time")) , ("cpuTime", (Just . measCpuTime, "CPU time")) , ("cycles", (Just . fromIntegral . measCycles, "CPU cycles")) , ("iters", (Just . fromIntegral . measIters, "loop iterations")) , ("allocated", (fmap fromIntegral . fromInt . measAllocated, "(+RTS -T) bytes allocated")) , ("numGcs", (fmap fromIntegral . fromInt . measNumGcs, "(+RTS -T) number of garbage collections")) , ("bytesCopied", (fmap fromIntegral . fromInt . measBytesCopied, "(+RTS -T) number of bytes copied during GC")) , ("mutatorWallSeconds", (fromDouble . measMutatorWallSeconds, "(+RTS -T) wall-clock time for mutator threads")) , ("mutatorCpuSeconds", (fromDouble . measMutatorCpuSeconds, "(+RTS -T) CPU time spent running mutator threads")) , ("gcWallSeconds", (fromDouble . measGcWallSeconds, "(+RTS -T) wall-clock time spent doing GC")) , ("gcCpuSeconds", (fromDouble . measGcCpuSeconds, "(+RTS -T) CPU time spent doing GC")) ] -- | Field names in a 'Measured' record, in the order in which they -- appear. measureKeys :: [String] measureKeys = map fst measureAccessors_ -- | Field names and accessors for a 'Measured' record. measureAccessors :: Map String (Measured -> Maybe Double, String) measureAccessors = fromList measureAccessors_ -- | Normalise every measurement as if 'measIters' was 1. -- -- ('measIters' itself is left unaffected.) rescale :: Measured -> Measured rescale m@Measured{..} = m { measTime = d measTime , measCpuTime = d measCpuTime , measCycles = i measCycles -- skip measIters , measNumGcs = i measNumGcs , measBytesCopied = i measBytesCopied , measMutatorWallSeconds = d measMutatorWallSeconds , measMutatorCpuSeconds = d measMutatorCpuSeconds , measGcWallSeconds = d measGcWallSeconds , measGcCpuSeconds = d measGcCpuSeconds } where d k = maybe k (/ iters) (fromDouble k) i k = maybe k (round . (/ iters)) (fromIntegral <$> fromInt k) iters = fromIntegral measIters :: Double -- | Convert a (possibly unavailable) GC measurement to a true value. -- If the measurement is a huge negative number that corresponds to -- \"no data\", this will return 'Nothing'. fromInt :: Int64 -> Maybe Int64 fromInt i | i == minBound = Nothing | otherwise = Just i -- | Convert from a true value back to the packed representation used -- for GC measurements. toInt :: Maybe Int64 -> Int64 toInt Nothing = minBound toInt (Just i) = i -- | Convert a (possibly unavailable) GC measurement to a true value. -- If the measurement is a huge negative number that corresponds to -- \"no data\", this will return 'Nothing'. fromDouble :: Double -> Maybe Double fromDouble d | isInfinite d || isNaN d = Nothing | otherwise = Just d -- | Convert from a true value back to the packed representation used -- for GC measurements. toDouble :: Maybe Double -> Double toDouble Nothing = -1/0 toDouble (Just d) = d instance Binary Measured where put Measured{..} = do put measTime; put measCpuTime; put measCycles; put measIters put measAllocated; put measNumGcs; put measBytesCopied put measMutatorWallSeconds; put measMutatorCpuSeconds put measGcWallSeconds; put measGcCpuSeconds get = Measured <$> get <*> get <*> get <*> get <*> get <*> get <*> get <*> get <*> get <*> get <*> get -- | Apply an argument to a function, and evaluate the result to weak -- head normal form (WHNF). whnf :: (a -> b) -> a -> Benchmarkable whnf = pureFunc id {-# INLINE whnf #-} -- | Apply an argument to a function, and evaluate the result to head -- normal form (NF). nf :: NFData b => (a -> b) -> a -> Benchmarkable nf = pureFunc rnf {-# INLINE nf #-} pureFunc :: (b -> c) -> (a -> b) -> a -> Benchmarkable pureFunc reduce f0 x0 = Benchmarkable $ go f0 x0 where go f x n | n <= 0 = return () | otherwise = evaluate (reduce (f x)) >> go f x (n-1) {-# INLINE pureFunc #-} -- | Perform an action, then evaluate its result to head normal form. -- This is particularly useful for forcing a lazy 'IO' action to be -- completely performed. nfIO :: NFData a => IO a -> Benchmarkable nfIO = impure rnf {-# INLINE nfIO #-} -- | Perform an action, then evaluate its result to weak head normal -- form (WHNF). This is useful for forcing an 'IO' action whose result -- is an expression to be evaluated down to a more useful value. whnfIO :: IO a -> Benchmarkable whnfIO = impure id {-# INLINE whnfIO #-} impure :: (a -> b) -> IO a -> Benchmarkable impure strategy a = Benchmarkable go where go n | n <= 0 = return () | otherwise = a >>= (evaluate . strategy) >> go (n-1) {-# INLINE impure #-} -- | Specification of a collection of benchmarks and environments. A -- benchmark may consist of: -- -- * An environment that creates input data for benchmarks, created -- with 'env'. -- -- * A single 'Benchmarkable' item with a name, created with 'bench'. -- -- * A (possibly nested) group of 'Benchmark's, created with 'bgroup'. data Benchmark where Environment :: NFData env => IO env -> (env -> Benchmark) -> Benchmark Benchmark :: String -> Benchmarkable -> Benchmark BenchGroup :: String -> [Benchmark] -> Benchmark -- | Run a benchmark (or collection of benchmarks) in the given -- environment. The purpose of an environment is to lazily create -- input data to pass to the functions that will be benchmarked. -- -- A common example of environment data is input that is read from a -- file. Another is a large data structure constructed in-place. -- -- __Motivation.__ In earlier versions of criterion, all benchmark -- inputs were always created when a program started running. By -- deferring the creation of an environment when its associated -- benchmarks need the its, we avoid two problems that this strategy -- caused: -- -- * Memory pressure distorted the results of unrelated benchmarks. -- If one benchmark needed e.g. a gigabyte-sized input, it would -- force the garbage collector to do extra work when running some -- other benchmark that had no use for that input. Since the data -- created by an environment is only available when it is in scope, -- it should be garbage collected before other benchmarks are run. -- -- * The time cost of generating all needed inputs could be -- significant in cases where no inputs (or just a few) were really -- needed. This occurred often, for instance when just one out of a -- large suite of benchmarks was run, or when a user would list the -- collection of benchmarks without running any. -- -- __Creation.__ An environment is created right before its related -- benchmarks are run. The 'IO' action that creates the environment -- is run, then the newly created environment is evaluated to normal -- form (hence the 'NFData' constraint) before being passed to the -- function that receives the environment. -- -- __Complex environments.__ If you need to create an environment that -- contains multiple values, simply pack the values into a tuple. -- -- __Lazy pattern matching.__ In situations where a \"real\" -- environment is not needed, e.g. if a list of benchmark names is -- being generated, @undefined@ will be passed to the function that -- receives the environment. This avoids the overhead of generating -- an environment that will not actually be used. -- -- The function that receives the environment must use lazy pattern -- matching to deconstruct the tuple, as use of strict pattern -- matching will cause a crash if @undefined@ is passed in. -- -- __Example.__ This program runs benchmarks in an environment that -- contains two values. The first value is the contents of a text -- file; the second is a string. Pay attention to the use of a lazy -- pattern to deconstruct the tuple in the function that returns the -- benchmarks to be run. -- -- > setupEnv = do -- > let small = replicate 1000 1 -- > big <- readFile "/usr/dict/words" -- > return (small, big) -- > -- > main = defaultMain [ -- > -- notice the lazy pattern match here! -- > env setupEnv $ \ ~(small,big) -> -- > bgroup "small" [ -- > bench "length" $ whnf length small -- > , bench "length . filter" $ whnf (length . filter (==1)) small -- > ] -- > , bgroup "big" [ -- > bench "length" $ whnf length big -- > , bench "length . filter" $ whnf (length . filter (==1)) big -- > ] -- > ] -- -- __Discussion.__ The environment created in the example above is -- intentionally /not/ ideal. As Haskell's scoping rules suggest, the -- variable @big@ is in scope for the benchmarks that use only -- @small@. It would be better to create a separate environment for -- @big@, so that it will not be kept alive while the unrelated -- benchmarks are being run. env :: NFData env => IO env -- ^ Create the environment. The environment will be evaluated to -- normal form before being passed to the benchmark. -> (env -> Benchmark) -- ^ Take the newly created environment and make it available to -- the given benchmarks. -> Benchmark env = Environment -- | Create a single benchmark. bench :: String -- ^ A name to identify the benchmark. -> Benchmarkable -- ^ An activity to be benchmarked. -> Benchmark bench = Benchmark -- | Group several benchmarks together under a common name. bgroup :: String -- ^ A name to identify the group of benchmarks. -> [Benchmark] -- ^ Benchmarks to group under this name. -> Benchmark bgroup = BenchGroup -- | Add the given prefix to a name. If the prefix is empty, the name -- is returned unmodified. Otherwise, the prefix and name are -- separated by a @\'\/\'@ character. addPrefix :: String -- ^ Prefix. -> String -- ^ Name. -> String addPrefix "" desc = desc addPrefix pfx desc = pfx ++ '/' : desc -- | Retrieve the names of all benchmarks. Grouped benchmarks are -- prefixed with the name of the group they're in. benchNames :: Benchmark -> [String] benchNames (Environment _ b) = benchNames (b undefined) benchNames (Benchmark d _) = [d] benchNames (BenchGroup d bs) = map (addPrefix d) . concatMap benchNames $ bs instance Show Benchmark where show (Environment _ b) = "Environment _ " ++ show (b undefined) show (Benchmark d _) = "Benchmark " ++ show d show (BenchGroup d _) = "BenchGroup " ++ show d measure :: (U.Unbox a) => (Measured -> a) -> V.Vector Measured -> U.Vector a measure f v = U.convert . V.map f $ v -- | Outliers from sample data, calculated using the boxplot -- technique. data Outliers = Outliers { samplesSeen :: !Int64 , lowSevere :: !Int64 -- ^ More than 3 times the interquartile range (IQR) below the -- first quartile. , lowMild :: !Int64 -- ^ Between 1.5 and 3 times the IQR below the first quartile. , highMild :: !Int64 -- ^ Between 1.5 and 3 times the IQR above the third quartile. , highSevere :: !Int64 -- ^ More than 3 times the IQR above the third quartile. } deriving (Eq, Read, Show, Typeable, Data, Generic) instance FromJSON Outliers instance ToJSON Outliers instance Binary Outliers where put (Outliers v w x y z) = put v >> put w >> put x >> put y >> put z get = Outliers <$> get <*> get <*> get <*> get <*> get instance NFData Outliers -- | A description of the extent to which outliers in the sample data -- affect the sample mean and standard deviation. data OutlierEffect = Unaffected -- ^ Less than 1% effect. | Slight -- ^ Between 1% and 10%. | Moderate -- ^ Between 10% and 50%. | Severe -- ^ Above 50% (i.e. measurements -- are useless). deriving (Eq, Ord, Read, Show, Typeable, Data, Generic) instance FromJSON OutlierEffect instance ToJSON OutlierEffect instance Binary OutlierEffect where put Unaffected = putWord8 0 put Slight = putWord8 1 put Moderate = putWord8 2 put Severe = putWord8 3 get = do i <- getWord8 case i of 0 -> return Unaffected 1 -> return Slight 2 -> return Moderate 3 -> return Severe _ -> fail $ "get for OutlierEffect: unexpected " ++ show i instance NFData OutlierEffect instance Monoid Outliers where mempty = Outliers 0 0 0 0 0 mappend = addOutliers addOutliers :: Outliers -> Outliers -> Outliers addOutliers (Outliers s a b c d) (Outliers t w x y z) = Outliers (s+t) (a+w) (b+x) (c+y) (d+z) {-# INLINE addOutliers #-} -- | Analysis of the extent to which outliers in a sample affect its -- standard deviation (and to some extent, its mean). data OutlierVariance = OutlierVariance { ovEffect :: OutlierEffect -- ^ Qualitative description of effect. , ovDesc :: String -- ^ Brief textual description of effect. , ovFraction :: Double -- ^ Quantitative description of effect (a fraction between 0 and 1). } deriving (Eq, Read, Show, Typeable, Data, Generic) instance FromJSON OutlierVariance instance ToJSON OutlierVariance instance Binary OutlierVariance where put (OutlierVariance x y z) = put x >> put y >> put z get = OutlierVariance <$> get <*> get <*> get instance NFData OutlierVariance where rnf OutlierVariance{..} = rnf ovEffect `seq` rnf ovDesc `seq` rnf ovFraction -- | Results of a linear regression. data Regression = Regression { regResponder :: String -- ^ Name of the responding variable. , regCoeffs :: Map String B.Estimate -- ^ Map from name to value of predictor coefficients. , regRSquare :: B.Estimate -- ^ R² goodness-of-fit estimate. } deriving (Eq, Read, Show, Typeable, Data, Generic) instance FromJSON Regression instance ToJSON Regression instance Binary Regression where put Regression{..} = put regResponder >> put regCoeffs >> put regRSquare instance NFData Regression where rnf Regression{..} = rnf regResponder `seq` rnf regCoeffs `seq` rnf regRSquare -- | Result of a bootstrap analysis of a non-parametric sample. data SampleAnalysis = SampleAnalysis { anRegress :: [Regression] -- ^ Estimates calculated via linear regression. , anOverhead :: Double -- ^ Estimated measurement overhead, in seconds. Estimation is -- performed via linear regression. , anMean :: B.Estimate -- ^ Estimated mean. , anStdDev :: B.Estimate -- ^ Estimated standard deviation. , anOutlierVar :: OutlierVariance -- ^ Description of the effects of outliers on the estimated -- variance. } deriving (Eq, Read, Show, Typeable, Data, Generic) instance FromJSON SampleAnalysis instance ToJSON SampleAnalysis instance Binary SampleAnalysis where put SampleAnalysis{..} = do put anRegress; put anOverhead; put anMean; put anStdDev; put anOutlierVar get = SampleAnalysis <$> get <*> get <*> get <*> get <*> get instance NFData SampleAnalysis where rnf SampleAnalysis{..} = rnf anRegress `seq` rnf anOverhead `seq` rnf anMean `seq` rnf anStdDev `seq` rnf anOutlierVar -- | Data for a KDE chart of performance. data KDE = KDE { kdeType :: String , kdeValues :: U.Vector Double , kdePDF :: U.Vector Double } deriving (Eq, Read, Show, Typeable, Data, Generic) instance FromJSON KDE instance ToJSON KDE instance Binary KDE where put KDE{..} = put kdeType >> put kdeValues >> put kdePDF get = KDE <$> get <*> get <*> get instance NFData KDE where rnf KDE{..} = rnf kdeType `seq` rnf kdeValues `seq` rnf kdePDF -- | Report of a sample analysis. data Report = Report { reportNumber :: Int -- ^ A simple index indicating that this is the /n/th report. , reportName :: String -- ^ The name of this report. , reportKeys :: [String] -- ^ See 'measureKeys'. , reportMeasured :: V.Vector Measured -- ^ Raw measurements. These are /not/ corrected for the -- estimated measurement overhead that can be found via the -- 'anOverhead' field of 'reportAnalysis'. , reportAnalysis :: SampleAnalysis -- ^ Report analysis. , reportOutliers :: Outliers -- ^ Analysis of outliers. , reportKDEs :: [KDE] -- ^ Data for a KDE of times. } deriving (Eq, Read, Show, Typeable, Data, Generic) instance FromJSON Report instance ToJSON Report instance Binary Report where put Report{..} = put reportNumber >> put reportName >> put reportKeys >> put reportMeasured >> put reportAnalysis >> put reportOutliers >> put reportKDEs get = Report <$> get <*> get <*> get <*> get <*> get <*> get <*> get instance NFData Report where rnf Report{..} = rnf reportNumber `seq` rnf reportName `seq` rnf reportKeys `seq` rnf reportMeasured `seq` rnf reportAnalysis `seq` rnf reportOutliers `seq` rnf reportKDEs criterion-1.1.0.0/Criterion/IO/0000755000000000000000000000000012505102676014304 5ustar0000000000000000criterion-1.1.0.0/Criterion/IO/Printf.hs0000644000000000000000000000642512505102676016111 0ustar0000000000000000-- | -- Module : Criterion.IO.Printf -- Copyright : (c) 2009-2014 Bryan O'Sullivan -- -- License : BSD-style -- Maintainer : bos@serpentine.com -- Stability : experimental -- Portability : GHC -- -- Input and output actions. {-# LANGUAGE FlexibleInstances, Rank2Types, TypeSynonymInstances #-} module Criterion.IO.Printf ( CritHPrintfType , note , printError , prolix , writeCsv ) where import Control.Monad (when) import Control.Monad.Reader (ask, asks) import Control.Monad.Trans (liftIO) import Criterion.Monad (Criterion) import Criterion.Types (Config(csvFile, verbosity), Verbosity(..)) import Data.Foldable (forM_) import System.IO (Handle, stderr, stdout) import Text.Printf (PrintfArg) import qualified Data.ByteString.Lazy as B import qualified Data.Csv as Csv import qualified Text.Printf (HPrintfType, hPrintf) -- First item is the action to print now, given all the arguments -- gathered together so far. The second item is the function that -- will take a further argument and give back a new PrintfCont. data PrintfCont = PrintfCont (IO ()) (PrintfArg a => a -> PrintfCont) -- | An internal class that acts like Printf/HPrintf. -- -- The implementation is visible to the rest of the program, but the -- details of the class are not. class CritHPrintfType a where chPrintfImpl :: (Config -> Bool) -> PrintfCont -> a instance CritHPrintfType (Criterion a) where chPrintfImpl check (PrintfCont final _) = do x <- ask when (check x) (liftIO final) return undefined instance CritHPrintfType (IO a) where chPrintfImpl _ (PrintfCont final _) = final >> return undefined instance (CritHPrintfType r, PrintfArg a) => CritHPrintfType (a -> r) where chPrintfImpl check (PrintfCont _ anotherArg) x = chPrintfImpl check (anotherArg x) chPrintf :: CritHPrintfType r => (Config -> Bool) -> Handle -> String -> r chPrintf shouldPrint h s = chPrintfImpl shouldPrint (make (Text.Printf.hPrintf h s) (Text.Printf.hPrintf h s)) where make :: IO () -> (forall a r. (PrintfArg a, Text.Printf.HPrintfType r) => a -> r) -> PrintfCont make curCall curCall' = PrintfCont curCall (\x -> make (curCall' x) (curCall' x)) {- A demonstration of how to write printf in this style, in case it is ever needed in fututre: cPrintf :: CritHPrintfType r => (Config -> Bool) -> String -> r cPrintf shouldPrint s = chPrintfImpl shouldPrint (make (Text.Printf.printf s) (Text.Printf.printf s)) where make :: IO () -> (forall a r. (PrintfArg a, Text.Printf.PrintfType r) => a -> r) -> PrintfCont make curCall curCall' = PrintfCont curCall (\x -> make (curCall' x) (curCall' x)) -} -- | Print a \"normal\" note. note :: (CritHPrintfType r) => String -> r note = chPrintf ((> Quiet) . verbosity) stdout -- | Print verbose output. prolix :: (CritHPrintfType r) => String -> r prolix = chPrintf ((== Verbose) . verbosity) stdout -- | Print an error message. printError :: (CritHPrintfType r) => String -> r printError = chPrintf (const True) stderr -- | Write a record to a CSV file. writeCsv :: Csv.ToRecord a => a -> Criterion () writeCsv val = do csv <- asks csvFile forM_ csv $ \fn -> liftIO . B.appendFile fn . Csv.encode $ [val] criterion-1.1.0.0/Criterion/Main/0000755000000000000000000000000012505102676014661 5ustar0000000000000000criterion-1.1.0.0/Criterion/Main/Options.hs0000644000000000000000000001530012505102676016647 0ustar0000000000000000{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, RecordWildCards #-} -- | -- Module : Criterion.Main.Options -- Copyright : (c) 2014 Bryan O'Sullivan -- -- License : BSD-style -- Maintainer : bos@serpentine.com -- Stability : experimental -- Portability : GHC -- -- Benchmarking command-line configuration. module Criterion.Main.Options ( Mode(..) , MatchType(..) , defaultConfig , parseWith , describe , versionInfo ) where import Control.Monad (when) import Criterion.Analysis (validateAccessors) import Criterion.Types (Config(..), Verbosity(..), measureAccessors, measureKeys) import Data.Char (isSpace, toLower) import Data.Data (Data, Typeable) import Data.Int (Int64) import Data.List (isPrefixOf) import Data.Monoid (mempty) import Data.Version (showVersion) import GHC.Generics (Generic) import Options.Applicative import Options.Applicative.Help (Chunk(..), tabulate) import Options.Applicative.Help.Pretty ((.$.)) import Options.Applicative.Types import Paths_criterion (version) import Text.PrettyPrint.ANSI.Leijen (Doc, text) import qualified Data.Map as M -- | How to match a benchmark name. data MatchType = Prefix -- ^ Match by prefix. For example, a prefix of -- @\"foo\"@ will match @\"foobar\"@. | Glob -- ^ Match by Unix-style glob pattern. deriving (Eq, Ord, Bounded, Enum, Read, Show, Typeable, Data, Generic) -- | Execution mode for a benchmark program. data Mode = List -- ^ List all benchmarks. | Version -- ^ Print the version. | OnlyRun Int64 MatchType [String] -- ^ Run the given benchmarks, without collecting or -- analysing performance numbers. | Run Config MatchType [String] -- ^ Run and analyse the given benchmarks. deriving (Eq, Read, Show, Typeable, Data, Generic) -- | Default benchmarking configuration. defaultConfig :: Config defaultConfig = Config { confInterval = 0.95 , forceGC = True , timeLimit = 5 , resamples = 1000 , regressions = [] , rawDataFile = Nothing , reportFile = Nothing , csvFile = Nothing , junitFile = Nothing , verbosity = Normal , template = "default" } -- | Parse a command line. parseWith :: Config -- ^ Default configuration to use if options are not -- explicitly specified. -> Parser Mode parseWith cfg = (matchNames (Run <$> config cfg)) <|> onlyRun <|> (List <$ switch (long "list" <> short 'l' <> help "list benchmarks")) <|> (Version <$ switch (long "version" <> help "show version info")) where onlyRun = matchNames $ OnlyRun <$> option auto (long "only-run" <> short 'n' <> metavar "ITERS" <> help "run benchmarks, don't analyse") matchNames wat = wat <*> option match (long "match" <> short 'm' <> metavar "MATCH" <> value Prefix <> help "how to match benchmark names") <*> many (argument str (metavar "NAME...")) config :: Config -> Parser Config config Config{..} = Config <$> option (range 0.001 0.999) (long "ci" <> short 'I' <> metavar "CI" <> value confInterval <> help "confidence interval") <*> (not <$> switch (long "no-gc" <> short 'G' <> help "do not collect garbage between iterations")) <*> option (range 0.1 86400) (long "time-limit" <> short 'L' <> metavar "SECS" <> value timeLimit <> help "time limit to run a benchmark") <*> option (range 1 1000000) (long "resamples" <> metavar "COUNT" <> value resamples <> help "number of bootstrap resamples to perform") <*> many (option regressParams (long "regress" <> metavar "RESP:PRED.." <> help "regressions to perform")) <*> outputOption rawDataFile (long "raw" <> help "file to write raw data to") <*> outputOption reportFile (long "output" <> short 'o' <> help "file to write report to") <*> outputOption csvFile (long "csv" <> help "file to write CSV summary to") <*> outputOption junitFile (long "junit" <> help "file to write JUnit summary to") <*> (toEnum <$> option (range 0 2) (long "verbosity" <> short 'v' <> metavar "LEVEL" <> value (fromEnum verbosity) <> help "verbosity level")) <*> strOption (long "template" <> short 't' <> metavar "FILE" <> value template <> help "template to use for report") outputOption :: Maybe String -> Mod OptionFields String -> Parser (Maybe String) outputOption file m = optional (strOption (m <> metavar "FILE" <> maybe mempty value file)) range :: (Show a, Read a, Ord a) => a -> a -> ReadM a range lo hi = do s <- readerAsk case reads s of [(i, "")] | i >= lo && i <= hi -> return i | otherwise -> readerError $ show i ++ " is outside range " ++ show (lo,hi) _ -> readerError $ show s ++ " is not a number" match :: ReadM MatchType match = do m <- readerAsk case map toLower m of mm | mm `isPrefixOf` "pfx" -> return Prefix | mm `isPrefixOf` "prefix" -> return Prefix | mm `isPrefixOf` "glob" -> return Glob | otherwise -> readerError $ show m ++ " is not a known match type" regressParams :: ReadM ([String], String) regressParams = do m <- readerAsk let repl ',' = ' ' repl c = c tidy = reverse . dropWhile isSpace . reverse . dropWhile isSpace (r,ps) = break (==':') m when (null r) $ readerError "no responder specified" when (null ps) $ readerError "no predictors specified" let ret = (words . map repl . drop 1 $ ps, tidy r) either readerError (const (return ret)) $ uncurry validateAccessors ret -- | Flesh out a command line parser. describe :: Config -> ParserInfo Mode describe cfg = info (helper <*> parseWith cfg) $ header ("Microbenchmark suite - " <> versionInfo) <> fullDesc <> footerDoc (unChunk regressionHelp) -- | A string describing the version of this benchmark (really, the -- version of criterion that was used to build it). versionInfo :: String versionInfo = "built with criterion " <> showVersion version -- We sort not by name, but by likely frequency of use. regressionHelp :: Chunk Doc regressionHelp = fmap (text "Regression metrics (for use with --regress):" .$.) $ tabulate [(text n,text d) | (n,(_,d)) <- map f measureKeys] where f k = (k, measureAccessors M.! k) criterion-1.1.0.0/Criterion/Monad/0000755000000000000000000000000012505102676015033 5ustar0000000000000000criterion-1.1.0.0/Criterion/Monad/Internal.hs0000644000000000000000000000224212505102676017143 0ustar0000000000000000{-# LANGUAGE GeneralizedNewtypeDeriving, MultiParamTypeClasses #-} {-# OPTIONS_GHC -funbox-strict-fields #-} -- | -- Module : Criterion.Monad.Internal -- Copyright : (c) 2009 Neil Brown -- -- License : BSD-style -- Maintainer : bos@serpentine.com -- Stability : experimental -- Portability : GHC -- -- The environment in which most criterion code executes. module Criterion.Monad.Internal ( Criterion(..) , Crit(..) ) where import Control.Applicative (Applicative) import Control.Monad.Reader (MonadReader(..), ReaderT) import Control.Monad.Trans (MonadIO) import Criterion.Types (Config) import Data.IORef (IORef) import System.Random.MWC (GenIO) data Crit = Crit { config :: !Config , gen :: !(IORef (Maybe GenIO)) , overhead :: !(IORef (Maybe Double)) } -- | The monad in which most criterion code executes. newtype Criterion a = Criterion { runCriterion :: ReaderT Crit IO a } deriving (Functor, Applicative, Monad, MonadIO) instance MonadReader Config Criterion where ask = config `fmap` Criterion ask local f = Criterion . local fconfig . runCriterion where fconfig c = c { config = f (config c) } criterion-1.1.0.0/examples/0000755000000000000000000000000012505102676013655 5ustar0000000000000000criterion-1.1.0.0/examples/BadReadFile.hs0000644000000000000000000000121512505102676016272 0ustar0000000000000000-- This example demonstrates the peril of trying to benchmark a -- function that performs lazy I/O. import Criterion.Main main :: IO () main = defaultMain [ -- By using whnfIO, when the benchmark loop goes through an -- iteration, we inspect only the first constructor returned after -- the file is opened. Since the entire file must be read in -- order for it to be closed, this causes file handles to leak, -- and our benchmark will probably crash while running with an -- error like this: -- -- openFile: resource exhausted (Too many open files) bench "whnfIO readFile" $ whnfIO (readFile "BadReadFile.hs") ] criterion-1.1.0.0/examples/Comparison.hs0000644000000000000000000000030212505102676016316 0ustar0000000000000000import Criterion.Main main = defaultMain [ bcompare [ bench "exp" $ whnf exp (2 :: Double) , bench "log" $ whnf log (2 :: Double) , bench "sqrt" $ whnf sqrt (2 :: Double) ] ] criterion-1.1.0.0/examples/ConduitVsPipes.hs0000644000000000000000000000232512505102676017132 0ustar0000000000000000-- Contributed by Gabriel Gonzales as a test case for -- https://github.com/bos/criterion/issues/35 -- -- The numbers reported by this benchmark can be made "more correct" -- by compiling with the -fno-full-laziness option. import Criterion.Main (bench, bgroup, defaultMain, nfIO, whnf) import Data.Conduit (($=), ($$)) import Data.Functor.Identity (Identity(..)) import Pipes ((>->), discard, each, for, runEffect) import qualified Data.Conduit.List as C import qualified Pipes.Prelude as P criterion :: Int -> IO () criterion n = defaultMain [ bgroup "IO" [ -- This will appear to run in just a few nanoseconds. bench "pipes" $ nfIO (pipes n) -- In contrast, this should take ~10 microseconds. Which is -- also wrong, as it happens. , bench "conduit" $ nfIO (conduit n) ] , bgroup "Identity" [ bench "pipes" $ whnf (runIdentity . pipes ) n , bench "conduit" $ whnf (runIdentity . conduit) n ] ] pipes, conduit :: (Monad m) => Int -> m () pipes n = runEffect $ for (each [1..n] >-> P.map (+1) >-> P.filter even) discard conduit n = C.sourceList [1..n] $= C.map (+1) $= C.filter even $$ C.sinkNull main :: IO () main = criterion 10000 criterion-1.1.0.0/examples/criterion-examples.cabal0000644000000000000000000000314712505102676020460 0ustar0000000000000000name: criterion-examples version: 0 synopsis: Examples for the criterion benchmarking system description: Examples for the criterion benchmarking system homepage: https://github.com/bos/criterion license: BSD3 license-file: ../LICENSE author: Bryan O'Sullivan maintainer: Bryan O'Sullivan category: Benchmarks build-type: Simple cabal-version: >=1.8 executable fibber main-is: Fibber.hs ghc-options: -Wall -rtsopts build-depends: base == 4.*, criterion executable conduit-vs-pipes main-is: ConduitVsPipes.hs ghc-options: -Wall -rtsopts build-depends: base == 4.*, conduit >= 1.1, criterion, pipes >= 4.1, transformers executable maps main-is: Maps.hs ghc-options: -Wall -rtsopts build-depends: base == 4.*, bytestring, containers, critbit, criterion, hashable, mwc-random, unordered-containers, vector, vector-algorithms executable overhead main-is: Overhead.hs ghc-options: -Wall -rtsopts build-depends: base == 4.*, criterion executable bad-read-file main-is: BadReadFile.hs ghc-options: -Wall -rtsopts build-depends: base == 4.*, criterion executable good-read-file main-is: GoodReadFile.hs ghc-options: -Wall -rtsopts build-depends: base == 4.*, criterion -- Cannot uncomment due to https://github.com/haskell/cabal/issues/1725 -- -- executable judy -- main-is: Judy.hs -- -- buildable: False -- ghc-options: -Wall -rtsopts -- build-depends: -- base == 4.*, -- criterion, -- judy criterion-1.1.0.0/examples/Fibber.hs0000644000000000000000000000067412505102676015411 0ustar0000000000000000-- The simplest/silliest of all benchmarks! import Criterion.Main fib :: Integer -> Integer fib m | m < 0 = error "negative!" | otherwise = go m where go 0 = 0 go 1 = 1 go n = go (n-1) + go (n-2) main :: IO () main = defaultMain [ bgroup "fib" [ bench "1" $ whnf fib 1 , bench "5" $ whnf fib 5 , bench "9" $ whnf fib 9 , bench "11" $ whnf fib 11 ] ] criterion-1.1.0.0/examples/fibber.html0000644000000000000000000101650112505102676016000 0ustar0000000000000000 criterion report

criterion performance measurements

overview

want to understand this report?

fib/1

lower bound estimate upper bound
OLS regression xxx xxx xxx
R² goodness-of-fit xxx xxx xxx
Mean execution time 1.534933170419988e-8 1.559289558335549e-8 1.5955027539726543e-8
Standard deviation 6.920776075641315e-10 9.603540851522639e-10 1.5315630337882154e-9

Outlying measurements have severe (0.8088974150289796%) effect on estimated standard deviation.

fib/5

lower bound estimate upper bound
OLS regression xxx xxx xxx
R² goodness-of-fit xxx xxx xxx
Mean execution time 2.0708698124838526e-7 2.1107084459065708e-7 2.1648984992614215e-7
Standard deviation 1.0816855360797646e-8 1.509440180252194e-8 2.2611667067984586e-8

Outlying measurements have severe (0.8225875438214796%) effect on estimated standard deviation.

fib/9

lower bound estimate upper bound
OLS regression xxx xxx xxx
R² goodness-of-fit xxx xxx xxx
Mean execution time 1.5092983334102336e-6 1.531476067375206e-6 1.5561257644394457e-6
Standard deviation 6.251710322835121e-8 8.358628655460513e-8 1.1570124318539241e-7

Outlying measurements have severe (0.6916115394455409%) effect on estimated standard deviation.

fib/11

lower bound estimate upper bound
OLS regression xxx xxx xxx
R² goodness-of-fit xxx xxx xxx
Mean execution time 4.0381903380782345e-6 4.1056747646400756e-6 4.177267574309266e-6
Standard deviation 1.967404221672586e-7 2.3166650962027132e-7 2.8018472343096967e-7

Outlying measurements have severe (0.6846724652533784%) effect on estimated standard deviation.

understanding this report

In this report, each function benchmarked by criterion is assigned a section of its own. The charts in each section are active; if you hover your mouse over data points and annotations, you will see more details.

  • The chart on the left is a kernel density estimate (also known as a KDE) of time measurements. This graphs the probability of any given time measurement occurring. A spike indicates that a measurement of a particular time occurred; its height indicates how often that measurement was repeated.
  • The chart on the right is the raw data from which the kernel density estimate is built. The x axis indicates the number of loop iterations, while the y axis shows measured execution time for the given number of loop iterations. The line behind the values is the linear regression prediction of execution time for a given number of iterations. Ideally, all measurements will be on (or very near) this line.

Under the charts is a small table. The first two rows are the results of a linear regression run on the measurements displayed in the right-hand chart.

  • OLS regression indicates the time estimated for a single loop iteration using an ordinary least-squares regression model. This number is more accurate than the mean estimate below it, as it more effectively eliminates measurement overhead and other constant factors.
  • R² goodness-of-fit is a measure of how accurately the linear regression model fits the observed measurements. If the measurements are not too noisy, R² should lie between 0.99 and 1, indicating an excellent fit. If the number is below 0.99, something is confounding the accuracy of the linear model.
  • Mean execution time and standard deviation are statistics calculated from execution time divided by number of iterations.

We use a statistical technique called the bootstrap to provide confidence intervals on our estimates. The bootstrap-derived upper and lower bounds on estimates let you see how accurate we believe those estimates to be. (Hover the mouse over the table headers to see the confidence levels.)

A noisy benchmarking environment can cause some or many measurements to fall far from the mean. These outlying measurements can have a significant inflationary effect on the estimate of the standard deviation. We calculate and display an estimate of the extent to which the standard deviation has been inflated by outliers.

criterion-1.1.0.0/examples/GoodReadFile.hs0000644000000000000000000000063412505102676016500 0ustar0000000000000000-- This example demonstrates how to correctly benchmark a function -- that performs lazy I/O. import Criterion.Main main :: IO () main = defaultMain [ -- Because we are using nfIO here, the entire file will be read on -- each benchmark loop iteration. This will cause the associated -- file handle to be eagerly closed every time. bench "nfIO readFile" $ nfIO (readFile "GoodReadFile.hs") ] criterion-1.1.0.0/examples/Judy.hs0000644000000000000000000000270712505102676015132 0ustar0000000000000000{-# LANGUAGE FlexibleInstances, ScopedTypeVariables #-} {-# OPTIONS_GHC -fno-full-laziness #-} -- cabal install judy import Control.Monad (forM_) import Criterion.Config import Criterion.Main import Criterion.Types import qualified Data.IntMap as I import qualified Data.Judy as J import qualified Data.Map as M import qualified Data.IntMap as I import Data.List (foldl') -- An example of how to specify a configuration value. myConfig = defaultConfig { cfgPerformGC = ljust True } main = defaultMainWith myConfig (return ()) [ bgroup "judy" [ bench "insert 1M" $ whnf testit 1000000 , bench "insert 10M" $ whnf testit 10000000 , bench "insert 100M" $ whnf testit 100000000 ], bgroup "map" [ bench "insert 100k" $ whnf testmap 100000 , bench "insert 1M" $ whnf testmap 1000000 ], bgroup "intmap" [ bench "insert 100k" $ whnf testintmap 100000 , bench "insert 1M" $ whnf testintmap 1000000 ] ] testit n = do j <- J.new :: IO (J.JudyL Int) forM_ [1..n] $ \n -> J.insert n (fromIntegral n :: Int) j v <- J.lookup 100 j v `seq` return () testmap :: Int -> M.Map Int Int testmap n = foldl' (\m k -> M.insert k 1 m) M.empty [0..n] testintmap :: Int -> I.IntMap Int testintmap n = foldl' (\m k -> I.insert k 1 m) I.empty [0..n] criterion-1.1.0.0/examples/Maps.hs0000644000000000000000000000600412505102676015111 0ustar0000000000000000-- Benchmark the cost of creating various types of map. {-# LANGUAGE FlexibleContexts, ScopedTypeVariables #-} import Criterion.Main import Data.ByteString (ByteString, pack) import Data.Hashable (Hashable) import System.Random.MWC import qualified Data.CritBit.Map.Lazy as C import qualified Data.HashMap.Lazy as H import qualified Data.IntMap as I import qualified Data.Map as M import qualified Data.Vector as V import qualified Data.Vector.Algorithms.Intro as I import qualified Data.Vector.Generic as G import qualified Data.Vector.Unboxed as U type V = U.Vector Int type B = V.Vector ByteString numbers :: IO (V, V, V) numbers = do random <- withSystemRandom . asGenIO $ \gen -> uniformVector gen 40000 let sorted = G.modify I.sort random revsorted = G.reverse sorted return (random, sorted, revsorted) strings :: IO (B, B, B) strings = do random <- withSystemRandom . asGenIO $ \gen -> V.replicateM 10000 $ (pack . U.toList) `fmap` (uniformVector gen =<< uniformR (1,16) gen) let sorted = G.modify I.sort random revsorted = G.reverse sorted return (random, sorted, revsorted) main :: IO () main = defaultMain [ env numbers $ \ ~(random,sorted,revsorted) -> bgroup "Int" [ bgroup "IntMap" [ bench "sorted" $ whnf intmap sorted , bench "random" $ whnf intmap random , bench "revsorted" $ whnf intmap revsorted ] , bgroup "Map" [ bench "sorted" $ whnf mmap sorted , bench "random" $ whnf mmap random , bench "revsorted" $ whnf mmap revsorted ] , bgroup "HashMap" [ bench "sorted" $ whnf hashmap sorted , bench "random" $ whnf hashmap random , bench "revsorted" $ whnf hashmap revsorted ] ] , env strings $ \ ~(random,sorted,revsorted) -> bgroup "ByteString" [ bgroup "Map" [ bench "sorted" $ whnf mmap sorted , bench "random" $ whnf mmap random , bench "revsorted" $ whnf mmap revsorted ] , bgroup "HashMap" [ bench "sorted" $ whnf hashmap sorted , bench "random" $ whnf hashmap random , bench "revsorted" $ whnf hashmap revsorted ] , bgroup "CritBit" [ bench "sorted" $ whnf critbit sorted , bench "random" $ whnf critbit random , bench "revsorted" $ whnf critbit revsorted ] ] ] critbit :: (G.Vector v k, C.CritBitKey k) => v k -> C.CritBit k Int critbit xs = G.foldl' (\m k -> C.insert k value m) C.empty xs hashmap :: (G.Vector v k, Hashable k, Eq k) => v k -> H.HashMap k Int hashmap xs = G.foldl' (\m k -> H.insert k value m) H.empty xs intmap :: G.Vector v Int => v Int -> I.IntMap Int intmap xs = G.foldl' (\m k -> I.insert k value m) I.empty xs mmap :: (G.Vector v k, Ord k) => v k -> M.Map k Int mmap xs = G.foldl' (\m k -> M.insert k value m) M.empty xs value :: Int value = 31337 criterion-1.1.0.0/examples/maps.html0000644000000000000000000047564612505102676015531 0ustar0000000000000000 criterion report

criterion performance measurements

overview

want to understand this report?

ByteString/HashMap/random

lower bound estimate upper bound
OLS regression xxx xxx xxx
R² goodness-of-fit xxx xxx xxx
Mean execution time 5.54613319607341e-3 5.621667703915931e-3 5.713526073454561e-3
Standard deviation 1.972562820146363e-4 2.494938876886024e-4 3.1487131555210624e-4

Outlying measurements have moderate (0.21993690418913867%) effect on estimated standard deviation.

understanding this report

In this report, each function benchmarked by criterion is assigned a section of its own. The charts in each section are active; if you hover your mouse over data points and annotations, you will see more details.

  • The chart on the left is a kernel density estimate (also known as a KDE) of time measurements. This graphs the probability of any given time measurement occurring. A spike indicates that a measurement of a particular time occurred; its height indicates how often that measurement was repeated.
  • The chart on the right is the raw data from which the kernel density estimate is built. The x axis indicates the number of loop iterations, while the y axis shows measured execution time for the given number of loop iterations. The line behind the values is the linear regression prediction of execution time for a given number of iterations. Ideally, all measurements will be on (or very near) this line.

Under the charts is a small table. The first two rows are the results of a linear regression run on the measurements displayed in the right-hand chart.

  • OLS regression indicates the time estimated for a single loop iteration using an ordinary least-squares regression model. This number is more accurate than the mean estimate below it, as it more effectively eliminates measurement overhead and other constant factors.
  • R² goodness-of-fit is a measure of how accurately the linear regression model fits the observed measurements. If the measurements are not too noisy, R² should lie between 0.99 and 1, indicating an excellent fit. If the number is below 0.99, something is confounding the accuracy of the linear model.
  • Mean execution time and standard deviation are statistics calculated from execution time divided by number of iterations.

We use a statistical technique called the bootstrap to provide confidence intervals on our estimates. The bootstrap-derived upper and lower bounds on estimates let you see how accurate we believe those estimates to be. (Hover the mouse over the table headers to see the confidence levels.)

A noisy benchmarking environment can cause some or many measurements to fall far from the mean. These outlying measurements can have a significant inflationary effect on the estimate of the standard deviation. We calculate and display an estimate of the extent to which the standard deviation has been inflated by outliers.

criterion-1.1.0.0/examples/Overhead.hs0000644000000000000000000000142312505102676015746 0ustar0000000000000000-- This benchmark measures the timing overhead added by the various -- functions we use to measure performance. {-# LANGUAGE CPP #-} module Main (main) where import Criterion.Main import Criterion.Measurement as M import GHC.Stats as GHC main :: IO () main = do statsEnabled <- getGCStatsEnabled defaultMain $ [ bench "measure" $ whnfIO (M.measure (whnfIO $ return ()) 1) , bench "getTime" $ whnfIO M.getTime , bench "getCPUTime" $ whnfIO M.getCPUTime , bench "getCycles" $ whnfIO M.getCycles , bench "M.getGCStats" $ whnfIO M.getGCStats ] ++ if statsEnabled then [bench "GHC.getGCStats" $ whnfIO GHC.getGCStats] else [] #if !MIN_VERSION_base(4,6,0) getGCStatsEnabled :: IO Bool getGCStatsEnabled = return False #endif criterion-1.1.0.0/examples/tiny.html0000644000000000000000000063426412505102676015545 0ustar0000000000000000 criterion report

criterion performance measurements

overview

want to understand this report?

fib/fib 10

lower bound estimate upper bound
Mean execution time 7.950250148027324e-7 8.087233523139602e-7 8.263881789521396e-7
Standard deviation 6.469576002518438e-8 7.962093335887086e-8 9.595188287095253e-8

Outlying measurements have severe (0.789683189845111%) effect on estimated standard deviation.

fib/fib 20

lower bound estimate upper bound
Mean execution time 9.397387721886237e-5 9.511279240520537e-5 9.683396722581508e-5
Standard deviation 5.084981483933464e-6 7.060410460215048e-6 9.916444086871226e-6

Outlying measurements have severe (0.6764999252677036%) effect on estimated standard deviation.

fib/fib 30

lower bound estimate upper bound
Mean execution time 1.1405421545418602e-2 1.1464177420052388e-2 1.166933422318349e-2
Standard deviation 1.5835878091381052e-4 5.030517750313856e-4 1.146763021342376e-3

Outlying measurements have moderate (0.414995643896579%) effect on estimated standard deviation.

intmap/intmap 25k

lower bound estimate upper bound
Mean execution time 5.030530741127831e-3 5.067442705544335e-3 5.11489753952871e-3
Standard deviation 1.7601420712288937e-4 2.14104721044797e-4 2.796949297562274e-4

Outlying measurements have moderate (0.39528660323872544%) effect on estimated standard deviation.

intmap/intmap 50k

lower bound estimate upper bound
Mean execution time 1.3004106333168846e-2 1.3085197260292869e-2 1.317617540589223e-2
Standard deviation 3.817067615429757e-4 4.4020726935288003e-4 5.281243811580562e-4

Outlying measurements have moderate (0.2967324863902443%) effect on estimated standard deviation.

intmap/intmap 75k

lower bound estimate upper bound
Mean execution time 1.772755031815419e-2 1.782442693940053e-2 1.794612770310293e-2
Standard deviation 4.572927417104507e-4 5.554628346393567e-4 7.805157733235236e-4

Outlying measurements have moderate (0.2673858721467461%) effect on estimated standard deviation.

understanding this report

In this report, each function benchmarked by criterion is assigned a section of its own. In each section, we display two charts, each with an x axis that represents measured execution time. These charts are active; if you hover your mouse over data points and annotations, you will see more details.

  • The chart on the left is a kernel density estimate (also known as a KDE) of time measurements. This graphs the probability of any given time measurement occurring. A spike indicates that a measurement of a particular time occurred; its height indicates how often that measurement was repeated.
  • The chart on the right is the raw data from which the kernel density estimate is built. Measurements are displayed on the y axis in the order in which they occurred.

Under the charts is a small table displaying the mean and standard deviation of the measurements. We use a statistical technique called the bootstrap to provide confidence intervals on our estimates of these values. The bootstrap-derived upper and lower bounds on the mean and standard deviation let you see how accurate we believe those estimates to be. (Hover the mouse over the table headers to see the confidence levels.)

A noisy benchmarking environment can cause some or many measurements to fall far from the mean. These outlying measurements can have a significant inflationary effect on the estimate of the standard deviation. We calculate and display an estimate of the extent to which the standard deviation has been inflated by outliers.

criterion-1.1.0.0/js-src/0000755000000000000000000000000012505102676013240 5ustar0000000000000000criterion-1.1.0.0/js-src/flot-0.8.3.zip0000644000000000000000000236527112505102676015414 0ustar0000000000000000PK +Dflot/UT &S&Sux PKt=D=kID flot/API.mdUT .US.USux }FϋH:KW[Zm^$"T$@`UEDfd7ZE<""QͺeռH%g"uU׾~yQuMͻFJsW櫼ofwt{ANw-ϓZ~7/euv"]E' 8G|Ͽܭrnw|u)ҶhʢMyPGN _:eB})/Wb^.u/J^z O8/nU/\o'[7|cR?JfV4tV.ȅq$ɣGQN[.&y^]rWƒIO?mۼ;9?Fu>/VZ`r'i z'I^PZ+}Z.^źO_o$*bJ~캔ȻW԰NUGo\t4(WA-eU7?|__f1NGu"EG.-ɾޡq7O0I4ĕ:)EEҀG%mR_L5-ޠN/xMW`k:Si*<*ntS*RԢI:u2phjy%e7󫏅7Һ9IlR({,N2ƭ V^HC[>ŬXw^ykDvԥIMK+j4,w QLN>ۼɻ&={BkDy F-QCU;zާ_R, t|Y0M%Ӓqb:[ѳUK7%usQۓy-uyo`qL35M^9Y^8t:WM4%a*n;i ϖ.F&xT)aЧmMw=ue~5/^g3d]xe/ka+A/w]_s^",{=mfaC/bMG1C&(.JjB芇_^+`G`dVsoL<0oyj4_ZKSo"2Kʹ[/@LuD?ٷ4Ce#4uCcZ;ޝY';eE op~[{urM-VG-0IфUaLc^͂xdW`׻YHP'(OuU7ݪ%h>DsȉKCC> j!iC~ 9Nҋ┦1|Q :=>#^m{ot,ҺOŔw|$OY7f9/1>%˔~,4 |e<1 `q0mMѕF YuI&OD7`f*I꿊<+jԖ"$#\\F:?8x2*X\i]zy 2.*gq ҍ Tͧ6]'ʦnYb/wku!DW[)6D&b3ѠfAʢPN!-;Ig&෻͖H.JX ΰA3&F߶'_ܱZ rfpL<n'>a \Uck;uC&>yr埤YihJidbiМL \!N3U'|40q~UY7Ia)*̬oRrL .|QDpi{#7C~Y >mf\ FIb6#09= r:~]ǟ)ϲGt*?Hg~~viXLU@m;zN(43:D;\5$$om.͜i(Y:?Itt5{s9=q"*1EM5曘]1&.D+*H")0 WUU"5O7KGoF }3voMrLÔ_J["5]7+"zۢҨ@8NӬa7TĒ8EɿpOY|c# Y5I+_Gng9}tC&%K^|Oļ7_C$!,9E/BAb;Z]V{$?75${Ytz!xd@seP̗/; >'mٖr-N> Pa@^K62 ,(![ 5<dʀ,!w!A/ L@ݷX@c')sJ4-b .,L !h}S6!fdP{.m`u! ~H'CĢ"Qϻb^q.D%#qs6kғE>_%P[?<'8iɄAl_h'gO0"kelSs,OGwI8֑{.Wb/k){iaȔO述l `iiB&,3s ZAcs6W@/<)ȂKb5k2t8+ "|Y7:V.?†O7#Uc)VUNxF< QC KyE#뺾Vf| $ E_eLCF<5ɴ8;)=)LDBz~6Ke̓3otmt&Jl+ʻA>s~> U"Ο5|4Ҳ#`;}TB-MӵЅKs7e:h?<߶zKuG3㾁bCr1;)nWsH'eޭBuoKK&U,aj_(bq)KIr-FS#:+7@k 61DݦpЂЫYԅ/vTMMfuep{tv(-޲co(E|ALM}N`yfaHzkl}dfJ ec1vB?K1}~7Xg͂t',Kz\tZ{.S=\4eʮ&*G4,=//%<136kGO{ܹYɍf36I%]bf—*NyL^|WX uiJ1DŽ9W45E$ `{ҞXa4 dZ7."-FQdbBmId -^KvO+ڹR¾KpOn$0aے`!9Jdze*_hJuNyr㧂 )N/o= 7v׮FonΞϲq|J6n)DTSO=bC_+X#:Z"7G]Dwln״F; Xi-ROA:ot, 魇( G Ve$Tpt]VjL|CzQ߶7 ytt8]v7L-z=$>sƝ&IW^eP hr @p观 XbYo6hŁOa`OI XQq-7/[~q^nۿnӗ_dek݆o|Æ~>tHmzLmKnA'~Ar۫V &iesEe>ly$xpUGO,.[@&JdHT׭8 sFuyZ=_ 5~y8M_40ᲪS&EPy"/#ߴ[HX% ssL?&Odh#SiϐMfKs:9d&4!@VU}HY3CKJ Qd#6#LJxV5^.u6tPy WN,Zԭ '%KMK(I͜3#^Kv!:=\TYqHP ϑh~~Q uTgd䌗$2%Qv8W'A4 nzӻ]R$ U Ɉ* {~3YzhFq73 ~ [ &lNW7Z5:hP1EJQrwRD@+#RCO|r]?^龾*u#>]=q&,C鿅,ɦ3Vtƞ"6 DDN5hTwx<%B`?UR Az̟f@FM˸"-׊$e0ۊWYL19ȻVn@l$s=-,vs&Wc  3"aZщ^rV>Ɩ3*9LTv6aMm)u3ޤENYg;zf6GYA{Dr%\sSk ~3g1јr +Eݲ&P邚,5*!D 9MH1,.]X23}]n.W_3SrT !oTY3y!#sTT$7ys b`^QMD O/9h Sf1S4ωnNkXm/b?8OUt5_eBjj9\l$'P>RclRCǃLp٣Oew#H<>n~n?=,bEz󻟮F^rA5%NvP{|!֓$J?7_+Wu+IbnǡouL7z +%a5lHT5+ȋN"":dxPk3M[:p-=J}?G^}'QdXZ:ʑ`$Fe~*|<iψp_a}֜';EkW(X7^m{3B^_R$  .L>>}AaѺ#hѵx9[1q&cF zޗVgȸ3Z aM vKp} z KQ tJby]hDuu͵49vζ* ~K^# G&Y_K2 ՝Sa U D8 vVԴ*~kV552cmҖHSdsMf8ljtD--~2L+HG*9 $1k )X TRv|bR" 1:$o= EI.A@%982M)wYRj?^6+X_ SG{'lUkS̛6=P FxfjK!` zrLL>c)ؒY 7 CڪkHYbcEC0Ը.NwlńN}2BpIr]oE {܋"4U-#I-mAeuېsD/j r)8f%,&% uz]_Fɽ wZvSGg^~ ze;~wq|~h)ٷ vOS)c>Iz yvr~>x zxsPp%{jw gjҿ"Kq% YӴ%șT}oe"+RƷ2]@+ XgV HVړ^,9srhԤNBdt/z(.Rhg\oH*+!*vPϱ7ۼ8blPn*˷zUvCo8ؑUۙgWv.!Mi3Klc |M(7܉tW)bpfiQڠ \m= 8y$䑶AB/ٯ^($=0H>vq+׋X/70ʁ1* ŻV8UNG܋Rk68fc(1Nr pܧt($];t9&o.8d:ccS0n^:u[ ,Ѐ4 4|xdHT 3֭"C$} ##$bCDIEC_|HµaMΜ#Az*(ce.1ſMZXq_o'Zg7bMKhE(FdQX?VЂo>>JF5kz7 2fz!I582>>ly.p)ϹbGWuS)c*]A&G'R!kſv0%}NSP<8jxO+`DTe$^׳<Ի KaTy`9Nqǻ827ȵ^}`_CL6gX֍^0TOkfޡx(#yw j~;ã8iAҒDYjJp1XY 0 Fu gR0^.د)lߍcdtsm> Z:$b'CK8KO8pZZ9HRvr˻rbeno`\9gWԚٌN2kl6=i  o]?GKŠwaņܧBq[pr;#k-Kz(ek;s-*:x9! 'ؔ>B%!"f^A$"<`$5st+ƓX ZUk-t*p\2\ Q|<;ds?= ,bO<4 vJ,Υ4Z,h"J!Z*HYmDs#l)sՑ7ގ!)}M*g'Ȃqk&#aIH0PMXK8Qp*CkP;hzYb-'sf&Rhg0n8N aQ8> g>|0|H;i'|c_"'I{zTJ3TgDn졻&w\EOiB:q]9)ՠ[/=K`4/6qRz)뚘?.Hils<BS5w4Y)Hft|u$ZTpf U >q[NK\Șzh[Ӊ"r}~>cZy]$6i;LiZ7獴ZK +֧;0D6T Xzy`qy1oCH2GOgs-f9YK/b8]M}3ڿc\i6 _xZp!O*GH҂eX3.1ݬG}hօۗ?8r}vU-P] /Z=,KIL ՛%UᢒZ&(ۭ֡sK}#0Ce%x<00V ޿-xwI \n xjœs/@ѝ`QNR-I6J:Kw&^  3P\ޜIYVgGU[-WvPH s&𐂤;jiaIM.e&ΜgŶ޲v`Æs8G_cHTv"N&NF/#uMfxLkz_c(<{e&VBsT'#SK%Ϸɋ91Cծѝ%,f+g]H;R2c6qi>XpݒciYIEMi?Xr'g=Ev25ԩBI<̽7'Û՜ 2s!GPB'ᜅG$LGa f YxZڦB܂Nl7vvph#s KTz zo33P/THbf=e]Ԅ,iɣs7^?)3n,%F>G{pg"wUʼnH-hvcMAI!YbBk( Һw?2 eEă73SXa7*oSɇVv5 p3 fS|aZ"yގ u"s(W4 6n%V`%?@ +3;+_1k qV^[YJŝ vvD;M܍zf;ϱpu޹IVxeXrR9WYzw"^r$fP\//LHIc.{N򞪰HS=ka0EvR1k(C8sɕcॐ'\^L.cPJg\};LТ-" A#1HjO 4EFX%jSwq35uJPnQэ3`9VIur=_]Ń{c01ܣai@ PbJ84=ةU-c_Kd2\l/~<<#w'w-5TVo qH-סJCPm?cyoLxS)ӐS(gXXxw8Mߙ !Ǧ]9י3s qhUhm$p%¶rvB~ G׺9T7%+4'ww1 Yc +iC,zv0lPIE5sHEZ^vZ@=9?59D3җ9p~SLi{NYJQ7A|sL#}O 8ꘆxtSiL%26]Uu *={#&ʨIp :&o4 FabWlOjE] qgVIuP㗫#h,'J#ԶEvbxKF˲q8y^+<8FR“ڸPpG!%BΠqFe2t3<-_2$\͵=gHA>+ %~%h|#H!{/nYNVH=TA~dH'; sYpR=D {=_) ,YtJ6 w/UრnmFP\DC5+CB`JZWJg+M5Xa(=`ict]g,<oh#CeiBJyfьX|X6T'ߤbrHl9*H#>ݜ@Sru)yI$=[tr+"8D&@a4>]^ H7]ӓ=Ç!i2Ʒgn1Q>PjoksR>iPBGz WlqELeEۣ7lu'i/ka% ZhߊySTIsfWt 4Q7,ڒ%".A$,)n Sua 8Mb8\%xZ"fh45 lW'X@XĎ@uT>iB7~X+c8N佃(Ь餼 %drT `j=[6ڸ)-8IBC1NJ;9<ԯX&['չ~M-[€a7q@(+yS:1+žt$wy:;YdL@h3Ξ?5x<Š`7啸-`IaPu 3 X } ɏ~ Iy#dDdzjHuŵe5g1Zam*{(&Aq}qP]Ar6//ƑniG4+T-;u*Gzݑ8۹44 N##?-[TE-R`NRiTϊnq[[z {A[ʜܘKbífIHs]DrZ&YkQtQ`:<,Z i6k< I#{5%{KJ"U$y× c6CV2g`aUG\,ŒզX-"{& &st%jk^ؿPr6([J)EҊRAqOi]+LzF}ܨbUM/F1UmQ˪էB &Ye$ĵfvhVyQ1},MJKAJJ5.=⸭ O84uQ&OM{M9=腢j3Nel^ד3!npqTi۵ۅy}44$> s9jX+ՅZ'QAsҊVŢPPeG=U^D1HpM%ܖbfꯐ,UE^5ROibv@SPZmC$5\L/6'(eGQK1 wh枨z(M=m52A_=LIt#~8M,@/{)T#&另W4ɍcL•I>T7˙PuO$Y; &rVR\2^Nnu)e 5k:o$ws}Ť' >B>wmM"N ۠QeBdyF? Ƈ~@f\ݫbH 1-}4DY)r5Q&⼟B<0K1g#11b8"} ]2#s'vA@: )7*U(j }(=+:x^Z$ xP-/@1 B !lNgQ$o/v;sT;U.H* mz~u]ecs JƂw-D-5S4"6f=OtkVH:4iY;Q5\\YF߯1 MgX 7ѠeC] IfD?Ni i!cF'NΫTU3 Đ ]L+<Uڲ/YkE;&lmrF G߂+jU@FڛrV$}My\E` F5&=fE˂'^z9dӠ~;flΊNGr) =2peޱE7\c5.=rN;rK7?y\v7YTgXQ;&=i7Cѱ#?Yݻ#{U-ȋ$Vɑ&ba3, ~^WU>yh&*XejbEzB]YI*X|M‘ex0Ge+Dv@#Vo_#|N(j:}e>TZphu:qfH52vǙ@뻋sլbfA#%d}P"?"ݣ *T%+[S)>?@􅖃S}l^0l/0-d`{;IG(bϱ>m#m R׾)9*}ڿΖ{+ 3*\[H|;5>t-/ö|` 8jXka(&~Ϩ?X@4ilZBsO?g汸UJnR9E#j`sHHťs+.މId ^9uӛs!kפ9EĹ|\:h V[,oQ2%!Om:t%^ C VGqHumV반Ov\OobV#X ͭ[Эؔdώ޾ J@QihvJ"J7vj#X1]F{8 W]]Tj,fJ[4Å$eN9kɳ [8~_J.Gˁ?W1CCKe> sP䩸wGF< hO9>QS| q˄}7>*^8izO",RmOZn]!SHbL;) ݟw mi5ۇA#v"-%dk)cឱXHaY,FĵFWyiYB:E9g]F=sk`QCOl 1zXbKO["$̮ SoA ۀe{' 5mYZT`7ƍi B$B4iں8W* H#br=㰴 gDcBnۼH=1FV 4Z/ݠvu '-J]|e| !ӵ':\3\GL,)箚V6bXGk {TaWg=0ٸىvJ'd6 R)n 1 .ӗv߅@&WBˡr$X+M(#ɽo닿b`X sП$JE#H^R^!dSXs/KEMUo_Kӱޔr YU:_qjƮ nh>/*@-d,->b%n2ւ$_#ԘٲH oS" `u˦p$MJ,/ҫa| t3V{k[X&59}hZ)nšq}"8kyJxBWjӋgtO=M~A KV]Sk [M [J fK6ϵM,vj}b,i7$UA?~\k]n~&SqkѰ)ĕT HOED…N0/.EFKtNZ<_`{\"qo@)j5QFVRw`">X+#Rcxwk ~,bS+!CeO^.[P"'-7nD奰QteW 7#u:,U7^`6/(TBnk%PK t=Dflot/examples/UT .US&Sux PKt=DC^<flot/examples/.DS_StoreUT .US.USux ZKoFʊMZE=TC~ɩ(z)))) DV1z_&>rpl hh>9ɝ~s2ؐKw* - A zCKQ2!(iQp7Z{ o~[$:EOF`oGI܆<ڨfƮlC2?=ժrOOo+ft &S7;ěEo4 S.7j[ҟCE=ɶ;"t8ix ۟V76?]{&d}gJˆ^,g<QHџP;jD&K&|>:1n Wϱ>r|Iw'B>߅HQb1HOFzc%O5ͳ6+=,XxIg`bTڑ^"_yGVԶF cr2 ^  +UoscOhO<o'*fK>/,[$5'ȍ06=k -t`UhHϷ ww|eJj"A mr iN?%{'ZƔ3C^$sJs?eK |c~{^$ tB9}@zO @ PK t=Dflot/examples/ajax/UT .US&Sux PKt=D^BI,flot/examples/ajax/data-eu-gdp-growth-1.jsonUT .US.USux RĤ%+%ҢT P#sM%lJbI"P2:RGX VG!ıPKt=D;SOc,flot/examples/ajax/data-eu-gdp-growth-2.jsonUT .US.USux RĤ%+%ҢT P#sM%lJbI"P2:RGX VG!ır u2F: zF\\PKt=D>[},flot/examples/ajax/data-eu-gdp-growth-3.jsonUT .US.USux RĤ%+%ҢT P#sM%lJbI"P2:RGX VG!ır u2F: zFP1c 嘀rrPKt=DUd,flot/examples/ajax/data-eu-gdp-growth-4.jsonUT .US.USux RĤ%+%ҢT P#sM%lJbI"P2:RGX VG!ır u2F: zFP1c 嘀B9z@rrPKt=Du։o,flot/examples/ajax/data-eu-gdp-growth-5.jsonUT .US.USux RĤ%+%ҢT P#sM%lJbI"P2:RGX VG!ır u2F: zFP1c 嘀B9z@B9 : @N,W-PKt=Du։o*flot/examples/ajax/data-eu-gdp-growth.jsonUT .US.USux RĤ%+%ҢT P#sM%lJbI"P2:RGX VG!ır u2F: zFP1c 嘀B9z@B9 : @N,W-PKt=D zi-flot/examples/ajax/data-japan-gdp-growth.jsonUT .US.USux 5=0ཧ #xF7c܌wWپ+Oj#Yҙ~œ}J " BD\RxrAFQ44NRDRenPKt=Dhg+flot/examples/ajax/data-usa-gdp-growth.jsonUT .US.USux 51 НS4MSPL(z/$M(}q*~#8_j433\s؝*sR1J΃0+XPøc :gj䯟zRj\Ty@Q8ϚW |HŇ/))@Sr3HPj9ӍqQzVd{̻Dm3"s>L _%9?xx9H[m -(EM^nmT=]`Bt>qQ7M/cv{7$̫8:>VBQݨmRL z%Ԗm{vACV[]_|qITr bJF@Cb|M/7<\k-rbrW[%=#b45&DR ˍ7 LeK4sa%]Y:ukp̈́=ک$kCOr"QXSE|@!􈃝3LEҤ$nXԞs4+Fk>%_V|_\0cݟUn}W;_׀b"6V ݰ-bD]fzp2 T_6P47qӻ?t 9D]VqWt!rkyE{n &rux OEk[U+ٔ[F:nP?Hggs횕&aN:_Rd>XNAhūQ؃遭IgOٯVYIF9.u ZÂ. v_hmNZ4ԯ k%2 e^c(APyW ~Cҽ4Y뛟 XU1F3 cs%#qeB.1aIQUsa:2YA4lp KCӤj;Cf͘k2{4Kp`fx;G[ʴ[ xҬ^2 My7U*/鳋<&b8&Ni$~9IkWh!KۚS(e eI-ǘ(iɻi6fRv7[UI0O}~FCqpcjſF޳SEY,?3)y^62uMrJp ro/haV;ðhڍZ,mC5.UÞsur F7kpOkZ-? 3MEPK t=Dflot/examples/annotating/UT .US&Sux PKt=DD= #flot/examples/annotating/index.htmlUT .US.USux VmOF~;9:NGiDHPP {v$)wfmHrVz_xxr[HczQtwE'qvqaE?yV(Z,b/Tz~H{?2VĆMNL4,t[_k0Uiyi{U=Hg:{cHr fCXa%~fGi*9 U8jQCrͳo4rέCi# nDr8;il-* Q {` q&w!$DNX2N⨑ƻ7LEvךնj׍Lwv:o.߅G$ttg4DH'!~ H餃M߈.C#J_tob!;Eq9Jscjͽ1'Fқ=0V`!ey}\f+Gȴ*F0'x Vت^(p"9Z `c8?T?lIV%&/7LY# 4uus`n|DR;Rk|yݰҼSV7$|=weL>WfwK5N+ID:NpSd>8Pxq1\[ i뭳vۉْ3* FЃdr?תD&xLr@ \w7a`8-dp!Y ᳪ<~-ey⭐WrBΘN )C ZvN U~Va A` X 1GΟԢy»c|C}82ajS6ދGFwc%Fl + ۙK ԈYoIƵvTY##+m.Ɵre|e..RbKi3+aQ.ȴXF chkddBX tn r+>ގchYZy1woF'ο !J…,{tG^k߈"NM=1qCn*')Utx C)j̙R~  lz)[$S.#721qxPh/w5|(, !)EzMUn%>d\p0GF#K.,J3i`u!%_NJeGK-TVp j+,"H5MeA6%OdQa~ȼ㳕ʺ)o+_gʵ[!xnVhLvۻ~#;}apyqh#nv/~yvnbK/[o?iz7_OWW~ڮn%q}-d߼]#9'>}x{>l[^Lr0~ڔSu%4gS'\ʁһA.)#9/=ZhӑY3e @Na}񃉬!l̑l r薵r1!W㔉Ck)čTY!dw hހw^ uLrJQ'ihhiZa] gLZ4dQ&MdN`)ՁkƤe9*6[2)*9c@IX0iuA.30 {(c\ڑ%ź4vmp\c9ϱ(]cv'X!;7V.ct9Eh,4(\\Rap|^GZTwp'-w!'p0ʐ -{f( r:11h0$+ dk!Ddg,cV&aB1o!߱ءo&'eq ' 7x⡓Qq$_1;)ءo!1ʔ2ud+1l\X0k {k`a}aQ=D`ҕy"SICdpbs4 0 0 uqc5t2['C[Jéc1:.}Cd Tt`ơZBh]#ٷ=jPw\:3Ⱦ@8!'N)jA D֠QUE.Ǥ+.YWqmUG9bB&Ku;B'yBtEkW2h-~!ӬwΝcR L3c҄\a1lj g`Pl:JPnc%4#: } 9ilBrC9bV =+d$`p%:Uy`6c"&5\)]*%VR:ҹaIBI-6R2;c/.IlE[J⡪l47VychPy[0IT$UdK Iړ*&;nYc%d]wRHܠZ= ȪI~V +AtYd ݎ)YlR::xfkꈡ8ZN0ޘqF䦡XgZHުph^Ykn'xǂL8z'BO8jU?V۷sA#\8xl4ܷkGG?۹+zrGP>ӎޏsFGxom}>}JZ=<̅^p$[߈>δa#otUڕ9΀OێG?F+XM@`^dpd]\39u2%1=zDW>dO>G"iгAyAz;INҏsB8p^AD'(6> |$FEe q8Gs1^ 1ȮPЃMuK<`;l=Sd#zH4RKgؐF/􊳓}&U|=73y7:/)e z'Lm1:29#;OY#8hЏӵ#KK~iΐo!Ñg`7Mj'%G[?Րu㊠gGJK8g3NTZgu FD-8-}|4[OG]}J` ݇|Q?\ݬn߬w=S{f-(9|=v @;P%Ɏ,>ib`7z݁P]n@V@hTx @/O6ow |. y*$Bl+];Ie{ס[>O{"J$kʨ:ԟzWϜN^LG[n \?\@Ue4b'Zf7-FeZ 0M%/Hpe3 HdkIIv.d1TZphqA0[./S;o%>$s+V8^*C++Yh@J j: D {ܢZ@g ! 򾲽 I N+*NtSZWѕʊ[h*m*'cthv:'B 5P9j+ۚmM';N}Bg£VC@T{dR3TPk F2L%#PZ4YAT6Ҁ2J% N&%Zl{MQIRItƩ)2)/G*@T%U4@ ժ4@U4an 5oO*\N" WZr+-i*B몡f&ZJD#4lˌdkΜu8])ٳ: n"Z-5:skkQYլ@ek-UtZ=s>e<6#[ ޏ핑 u@BbU .@`=> , 6 6hQrRgL)|\r*β @Nv$`|T4\ ʵ#:IҙZrH)l] :96(kzrvqpƳeJ>l*|=Wcذ-JgƦ_h U\_rBkfT5cm.mɷ @˿7By$\vhm #oQ[o8z9@e]*dlNmqcԦBdlN-$j-g-]@ 7 YJZ؂X-S&9l\ wh5 p'Vu%: ٛS{1lL$x1s@$Jp\d׾pՉ%i#9NG&08Mp7f_$NDί5虳oUD,_,*0p 8lScn% /YV*iӄH^N4bi,MP Q7N' '*m춮@e ; VJRERe p`q`t]zIANS}$]a$$mN"!GFW!U]t0tjXEHEePo*m~!邡bFAKT]JUL`s% t/q%d.U#^ATd xFR HsR $FHY=[tPMLJ 2A*D*ˠR$<$̀2Nj+9>P8GTFծ_hv+\68ݔefsA'{bT{£a*\+pT$iZ=~hxVUwC5H TvpIp\R2['So,i7q {T/qtb?du%ٛZ'Z5UυS|a(WʈM ؟9e\~1-dmX 6wˠM>o(xmNط t\5nz2Up Ù5AߖAzOYf0qdkY"d5bٚv7q9{Lx;D-EX ۚSVʍjfNx3lz5r#uW}Ux\t\zT~hV`# g zHѻLXvmF3sS!\1(s榶.K-d*)+z2Cz".= it<%ЉXΉ# ĉBTå$=I*UPTxIlV0V̺ A[b.!y.MQ7Pe.!y TUQtKOV@K˄)UҤJ'@lUd[N]&$A^*/ni `~3kZ3-e [S91ENIJvUBBY?ܪjުpb Gw |։Fvb#=:c'UĂ /teLD˄L 'b'"O Matp"د~ع9s#xvnVܳ*Pܬ~a { s O$J M=Q䈠s03lmY7RTt$+Ë1Fj,]o$';?쀾4Tt$;dӣ&^U/0>zVuMpf6Rfcu2%\nv 4t3.RxWڠt=/2z9}:69>2 ' 3Tz̞va{ydQ,g k-4IC֖tg zįWj<%qٻ*~vݭ&z { !.XU[f 8N(Lfvʵ[5>MX5qqOn=5|įn CaBߎFdm\hvthY%SyBE<|1|1O]̃^4;<m=ww۽]wϦՇC'OniÖ|ڼ]m?MZ|.1~{zi>tyߨoWW뛻z6ߦ~Bdٴ]޾mSMO?l1lų~㟾?.>qk"]{aOߦwka~9\M?}~}rq17~=vi7oDШAދi.b}nFfoooַ/l~qP¯awg\>}q]|ڊL88>}ZTف끇h뮒sֻƠ훡ww=IB`IEpu(U\rwݴ~htJd^޸WU46xo?^mW/wWlxuD>~m~z{,mBN?inNwx_Vzw&CV~Hal2YZtM[VZ[ ]e^]:=wL6o{q&?>e[Nv});޼yef-n8,+2z|?\wy0Wty}%&f˻wWOpz>;bZ^O߉¾]=ַOu 8}PK t=Dflot/examples/axes-time/UT .US&Sux PKt=D}OG"flot/examples/axes-time/index.htmlUT .US.USux \koǕ,l6+!԰2E96A%Mr虡$&S}oMegM[UunzAâ;=?_6junzb Vכ78T:?fy9|w7i[`;_<|uwsqlo> ƒ7]v_}x'`2Ogq!.x0>8*](/L nY1 d]fK @e'v']p.3WaBP<$V !~^HKh`6{=æ,$m0a`$B[Jl*IʮICoش^5>X*Q{.ZȪ+ӻq>@e[ބt\`]{zC9L^%&]֐e63,f]>I)س.D=N2JR]0% KtroKhݱ ˺uޱ.O7/KnTv޳r]KծqpJT@k7 $`\fBîAt%y+BJS P c!;3u!$KyT@'d Vjc,Յ`r>U7g8dDՕI7Urķg]ixDVɠgw]Z=74&ZH U *&< .{hкO |5u [ ojCTԚo%Bcp3x<)W!B\\uF+Ǯ!6! `9d@%FUmu.ڡѕgB5-U} 2:6moU"w=[!T 5c;ׅ{jb1ր1ØQ;\] C2,C,ΣFhi⠚ih}OG'>B PJ)z0§96ޢ$ ztѝj[5TBoF|Re[+B&¶xVXٵ wCB6侖CnXkDup[*i!:{>k2TZ Q=k3ؿ<< bR?lT0W7VF|y}i_p6hxO<$ Ҧ~YŽA>!*U6]F< R Q|J9rxTM4$9h$lhnd*OЂ Ebˉ8;eԼJ>5g'z5HSd<*ðpH98pIDrII18KFM{#Q Ev Q0=p)NV+dHqtEFq';+6D( 51E('y3,ibP)TښKaCsrunSFS`>G A-Ցe=\5sj84:JМ+D 4v(dzBG4 %9B7ޢOgK+2 2=%H we?&$Ory'Xg[߬S@}J2;ғ֍jOƓu⟥z z\`(WB^.q9eg]6 P'ӈ0ϔ }!k_`3y=To.q4:{~a/I(3ڧ } ?XΛwA =y6T-͡NǡHGC,2BqQˬ^SS'7ӕO0I\Z+BhثVqL:n" Q~(K'ղh\A N@zz^9Z? ,o%65/x}j_|Y|CpC3#-$1UDzh;Tqbm1:}G %O!+M:)qp<Y\:AʛE^mE XD{,.qYu_AÜ_(i8j@|!{ ˭HyH}9ʛڡG1Hjigt֍&G|fJGƈlGOEZ|(JsGȥF(k[W.uubrTB^'t)>Լ L!hA7OM`I3*q`;JcL2G4_پ2E4r6}ů< X&}['OsW-'z^s 2R{n ?,tܾFҠgOF.7q0Tzrr\~Xz?nv׺˗00?W,}R,@G<(z `ty*M s9KuEĤHui O|… g`k84}SBD֛܃~k> &>@cn#<:a%;xsNہzCA|] %;x4s#~`s ; WO< &փ_?Gl4)~Gz}s/ Nt9p?+]pG .}V{cnf <\(8i?{ }ytyDЁɢalx#P2и:UI)3%@:^Ү;=6W<9'A^ fB@GT^2Y| ;ģJYML#HnjtvUGJ-$6Ο4?U"ԳtLO*yѩˤzM,8ʠ OyC@PJtFmXb779$W p|0i'+TK=rOd7%(kT|  C0&a!8;S RϠPOOPʙB.4UVzL:sJ(G<~v:<;}uJzM8m=ÞL6^/2,[Sv=[pmn?=pb[ÁnR(BO_-]qzKqm|y<=ޓ,.{y)'r|e?sкB춯OƴOƋ%IIbѤ0a1vؼڈ{IYl#wňon:3]?eΆ6ߎo6WF޴Z+n_[`pٕ>l[u7p:;{]}ϊ+W+wҭ7{D{rI0?jv&qr}/?Ng Z(;<_IݝtA2֎ Dlv߭ծ,W}0Dj..l{{ۼ_+QS>;PK t=Dflot/examples/axes-time-zones/UT .US&Sux PKt=Dĥ}j+%flot/examples/axes-time-zones/date.jsUT .US.USux \v۶@:Ȕ\mGFvR&^ !1Eؑ{Z۸EsdZ o7d;Et:l8lx qy1b$l]”MSu 026W, F%@V=FixL;NbyǘM`c`FK✈@#$ $J' i0I< K$"b C7&2l_W I-F:*XOWOD 6C |1K;۝i㰏!A3/_]G|ɣ0QWDt!"o0 "fMId"rvO#¾L&1xPk<[BE,f7 d\o:&"_qɖTѺƪsO 1#$n)FLrJ6-h3L^"`"&"ލ2E*Rd&,xCΏ؏0\"o6O64kQXM}!fW'f-DxOal].}h -fHͲ P~v .%\@6 JVl&j8瘰\-@4c$Yu:_ƝLJAo ,)g"W5W!5*Y$ #&<ȩiRИarҳMH>NهYdx3vxzxx|zW{~|fI_I@t)\sK1!/h,3f ƽH[x\!ǎ]g񂉟dzx5ü%b+qBpIX% mۗDwY'2B, n njGgËǿo ZSYo!{~~8 31}]6uηn[>?4ZڏFFLhE RXz$Glh=#tOhAz-HN2&YnN/Y2GףG&::?g'NM` <^JH–0%-!HK+ŠHB[SZ|GG ڷ|=tKCj$h Cp0F^0,WLZ(`_ݿn@-PSs5PCQ+7CpdONb}ɼEmQJmAv~yJf/V7/U\QE=A\)uvthΈ0@FVJ P n=a==}d"LQK:I8<6[=UKl46-= |]S4;*R5 ClOU`zJ>_AAr7z}hu(Ns;&!u?Up#SZ[lFhTXE@<^a nفe L9̬8ADQ\F *WdRRPbL˓ 6ozB);KQų=w|Aih_ AwڕsTNFGh6ޡ&%f rSꊋQD%e4e !+ɑ(J/fLU5N dWz H[ f@K8jiɕɱJ0[a~7<5&c2=0-=uO/g ,+ί -X,2mJTu:@c&P޹z" ȌKT*s7@hcӨ7z$H\ˮf6ɜ?u9>æ:ݿtVcY"8,W318tbj$]7y3gUTޗ!;$F-عVs#c4t9(GO^|V}6(FfFzO$z:p,GhZyʴ{B/CƑuLT>nSagacZv"p#CտT>[Zrsv;* [c1D4bGy`]x.uSsUs*?-je j}oɳ%t%wJTna)*>MGdiW楼QT CZDg14;COE5L'{ȵs1T9]G N2─D^ QgrA5*Ё9?DtɢV,c FzG7M71nfP7y>l861Ay$˗AF5) 3Vï6`E搗sA Jሼs,ȚW/}T bMU͡鵬$2Kת>[Azj('Vwa S(rib=lnAEh:Dz_VVv(eX M+ƙĄM.WCt:Etٳm6Ѵm"Mk)"wS=%7jV̕'3+ͭIʔ5oRj,$Sh{PGD|fgvV$ 1Օ?ȄE/)e$ʌdT*4%!O_ \onS%skى4$%K 5K.rak^P9ZS~ X5'jB[a!*Fv[T[])ï-^r0;F!YUq?PRf=Fq! b@īA\-uàʴn_Ui6jYYJ J_7[V>iCEw$ueYT~M\+_ 㑠5lu\PP ^|OЙ_CY'z.):.zZCGUMaakMuM SWumQo7j 6ZO}[ Ue}5:;K6mM~hU40CBІg xT8P.Ȏ;4~-z9PPy YU81 v!WUu\'&82)9XfڶvvA킠@i:*C4lKȎ$.MSKΙ~ rI5pQ6v..ftyڑC|,L C&_ Kg.AU*-0ۀ"iz+fZ/":D-- bR9BJBQ_T%@UGG>P?lĒa.p"}`^3yBpbz?n7|tgZMP*._`$XsZF |tz]u2ײSw!O,M nv[mu=dżzm溬b/'zlsPnkE- {8d3Jd[d&9-i``䥠C԰a6ϸ(uغw {t鎉ϟm=#rE"5^/}N-DnI3d6(@=XS{*!;6 b ~AW~j$ ~7]zwK, Jfi_hhofG[M~a-izN 9k:szP*w0H,}>ԙMqII=,$*5*`} <{!HM*4ovI-@O% ŷS̒fGרhCLt %v9ʃG\{÷|ȓe:$uWI坩ڳO|@b(} >k*ڭ5g,c١«Mz;wyNRB(~H_&c?8W$?[lsf ҵ7#ÊX{u¬ _bλ~E×ըSP@`eйE۪F 6pA#DT*YɘAD~aE;lJKQ~¸uUd rIGnòծ+oRҝO r<6[T-U t5|gFDᖺz3؊hEC/=2m q4]lq-Y`|`+ g趀E]IK=-L&6at¯XnS u fqxo//"Ϟ:Om-vZElqwdA@oL=}R*[@|k]Z9;YteyL}VҮ]=0j };<*{ Lu'h7z!:0J\&,uub˚apԯx7>W7խ .OkǞ=񶴄=4VR 9 OFoZ "Zn3C}Arq$wk]D:s> \y}!yɂpVt^`xί$DM5^i֍nh8OڒUt>K858fE|Y< {QpƎ49tțÄ@ϸ˫6f%tuE:MvZ/E0| 0p:L'B r'[~q_v7I{܋^5}\NiZȕZơM'D~כfU9jg$_%OC?R4 9 CBrj25$ I),/ Z&l"lTĶ'&`?6η$flYHAg?l.9YBgA=sMSj9/-U?d3 [i.8#M˻*ʲ_xaoSx]QͮHREE@e_/'|tdָ9v\AGIc-`eimA)b rP(\Y KpEJ  }yD=?S۷IF|'"#\T֦tIvn!0TK3$(\lLgZ7Pxy=1B+:j sml0?֎؊U#A[NGᏍLnKD&k%OԥN]YLkb*^d(# F]zuko4{fKFo>mʎXc$ҭut$-# v~c"qt4X+O?dVmZXǻ|6lQf`Y # ۋ'lHK˗N.:{_YkwwN!_9PМCzr/xM\q?\= { x%h0l.: C_a7Ԍ-[߅".&*\,v7M)qc[z]ȯwi1Vlm@^bN?Bh0NfpH!}r8`W ahً,uvlȇ-qt(H@l|y5ΓT~NH٦j2}*,Q@wn@y>s[ u`-?+9rHʡ!d- DMf =KL^Hh{aתXEatJYA&l=r}IƗ쀋PȻv6 lvے, ܺbn˘(kg,m%ڎ? LN_dA i9\L&I_f"u$1>> A:0;kbl:.J /'/0;`<-O }@sDËG%?~mn kĒl5ɺYM] |^~-8_o(Har Qp~2q?&i5ʽUg ?^>9턃ʐw4\ҒT~dpl|! '^p:b\m"s!J84$Ф1a4;<`\*^$eu7'̈>SwyuPR#)RΘw <0{ŋixڈ&Fذ=Awkֲ)9A2@#uޙO?zCXfns>0ֹZ#G,5B ='9mop⃱@ܗVa%y<_%"+Ps/n1+>4Fy{V1At-"yu[Hbj`-lL$9\5‹VMlH3pθVr)v)q}81zDc.]c4ntpȼ] IR>ȼWq^ls5ŬjDv#zAO.qcՇ!bP,l=l<UBXX75.#@ NVO[G&(ab<3hFgQ-p(18ow 0ʉ16V7SȠ˩p~ǩûg{~vuu.+7Sl F ݮy帍j׫Iل M#fL(oui>n4:Y5Չ~dC8\, >w[]:X~MA'0M4t/n;2n71†=OWI]_IGS P?=L3XD7a ȽlkhT1yv3uݮ/#*j_N|\qWcw4Ӌ9Iyt9֫#fǵ'&_x&dJi:VhVcLj6M?S/aeQn.0 ǸUPJCk%{:3sYtwg}dJ{D=O?F]gv (Pk:v OV-[6:Kii9bBP{E)iɍ;s)\Sݸw}o΃:,Nwrz5* Y)y <yg@~K6wo&+l'|+*;]$V+bJmlZ-tD[TOW_WSGP|'&_ zms=lںg =SkYGc4}0ZڽpziQ48=IJHM/S]ܱJΨؤųφf'9u=ߙrn m R:u8yQk_C|7M`Q(De^ ݋χR_B=3YPl o<5; :&41S7!5XƱo#>;G(m" Q˛QQnudV,"(A+TIbΛ@qDYCT誥?tV0,FjS+/4P<dD6$fl291eN76B1fㅾy(vڬ"jq:N@HXK{xGu8uN{UAai(mL}/[`w |!$ U5^*߁vOCN-pكF7ATBO^i|Ww3J\B}Zt" ޙ\}m7gGeiJkc|ɔ2!ۥ .f:^<|S#5jPKt=D cz (flot/examples/axes-time-zones/index.htmlUT .US.USux moF_;bNΰɩ&j}Z/`m6ӝwq҆nڋdefWwEw.G7C ;CJWt̶E/H eҥt^knj9Jd*ӤM/MmY-[`om|ڪ#O*<ȓzlGZ<'UdiՓ֎ӶwYv١5 *D IGgu#'Z[n#@VSVS~WSW:ƮҲV+rG"w.rG"wt/rI#7=ՔT&! ǃ8y* joF`ߒ]|wӟ(7{Ȏbzv/~Luzc?Xp}PyR}[4×02K882^!D{IH25m|=|Ձȇ[Fl]JϥE^_PK t=D!flot/examples/axes-time-zones/tz/UT .US&Sux PKt=D{Ұ2fBU:dB21Xq-gRfwAԽnH'T3~+C>2*n<ˑ<bŖdž4Y(-[ۨh>jͦ"Ib|!8PC&B1~7#Ȇ υaKs6SE,4X +2gijqB4b\ݺ۪ C*:3KX08 @412DScMb@7X1$GG*RP]Ġb@9J"XvM31;blt:a~C !Z Q$쒯ZXi8)ɗ[3˛ZuWJ'%cT aD:d`!41PXq 8/F#6\\\K0"D# 24jf3r *PjfG'0ͼ *aЂ)k D<5K.XA@t 52j!u*bi 1QL|*!GQC\>7LQȮTgr6y@cb@٩1|5gإCq @72X ͣErdDO!.)R?!H0O!"dl<7ZQcZx $-bTMrLBXD)riH/SnNl4ì$ ]KNQAasQ}P6D{*Lb^Gs4jQ{iDA2\.F\ 8!{ d$:Qx&Lh5l.F.2GijԐG[)K-((#ys}(dT,7fiߩ8+`a!bR|УݮЙkl5[ouA8-ЎKG $L|/M ND!m i%R֙,NhHjBY^hTQeG6jaDiCl9`6gI.'յ Wp݁ppN1&EX_)G҃[;&wܣ{,C)wÇmpR}z/JQ#ʡ#w+sc4'_z9yFbx]Sw~Jck;>j}cę񏯼|r:Ceh6xzP>([{e6D앵ߧV!D-=xmJ;WLhu?jXPRgPw*,w3+LB#^{z%8m*f2}h;l%;_aھWb_52( }6G.組$F#~O7?^Aӻߞ_M`\qYݹ<<3gdt@12lg+B302mwH/Ns.1+>tO@k t[ ļAat{ =ro)sY2 N)[.[PXd9BGpBA^ (Jգ:p!  xٲͲJUԧܡEx~Um=G25sa5 ۭ!8d~IYG-TR63 @̦FƜF=MoSCbUAG]pV۪. |t9M5aWRGSRq4}9Wn3cw>|%/B JJdD _[A+ >X yz/֓:|e)ͺW<'*'}i|y*9 \iDޅ_wbNK2ۼlsvWlCR< 7bpNr)hۻL" tnaly8KhƂ,XBČ͂RWٷ{'E^SonhvQ^kͿkͿ2e`"ŭ[r|-uIg_%^r>2{y([^uswkx7JNZKǴm 9^ǹs ITOXS@۪"EW ! t;*stWʦ{D 褺SU L-i%+A{~_v(*p'dvʃ7gs4dG=O(s<;Jp=vI]ї=ڰ+A >msoP?kY[z^m}y  <% T"a!xZ8 tBpD87/a %˶eCsRQ?Lb1İ 3 [&{oIHlUVZ+}{8*`lEznhɍhe#P˦ En9dQWd5%}$_b6Ň/%rۍEvYxv7@4x~onzg2w$b61vY|Phwט4&܁[Z?v;ZP6KR)nX& R7]2Lk_'US#9H*sE.J\&tMt|S$>\y{x& T&X2zu_ڤ jC CT`''RGSO (䖒.Ŷ[R.WWB5S3ZD-ם!Yk!U:TU6(~tЃ83KS8$rů:a_(Ct::Aegs-搠I>%T_du$4(cIdeSx0Hw;kHa@p۝G~`C#(Yw  x q3S vƖ.f8.(2' P#״4piVP)[&Ȇb(1Q:OM/BfwJlz'rJltiw@=LvZڽAP%Xb,pNlsى %( |_o!yLw a\-kF7ԢqV˜B^R&h P([1}>e+2% ASAA#r|@R},ubީD6-6t2x<{9y?~:g~#=ݕ?O%1rb[Rm_z6=_:!Y6 HxZ5Kh6&qPC~L/ns#T9ǐ qH_A#U{Vq{ܲ9woğv0rO/QkG<@Ĉ:_[ףCk#杙m*8s8 9=*˜l;bL@o} Yo86fo5"OS6; hHϢ4CxXx&ZI<~j+>v.sBc) 8>D ~iTPG5QU1~mlW2 A4iV'p8; 7o\F|5QhTXE`_a8,kƂꟳʇl(i6ZBa o>mgS&'S[tseP<_\gVi]>2~t}[窎dL]gdJ3*uKO]^<zūv*nEzP݃[_* .>Lb:x:+:.6Ê&a tGS'vɯ8d!lԷ:w;&F}[LֶnZ&̒k2m5[`֚v(v]u9:]dK,!vXu}7NRhK;6 ׅp\Ơjmfz`="rM +%Czn%7pV}kp8Y Ohʧdg5qv)i[Ƚc{[|9Oo=pxСhwzL |Kq "ڦͅE7 vr}reE}ZH8&ZUC )TFoX]!Vg1X4OtIZK|/,u]Vz= G'n`SlW f8*)k];Zvj63^~:<9sLD0jS ,e&=8mZyn9dPʯ4gS th-)*[ŗ5`St^;V'5WE .QJU$*N[Ty w&O]RVVU:nv~}e#x@Gvh>RX j(@RGc(RB =[A0Ί~-?hrw:'ζ|XDq7A! H%y;/UTNP-!&CRoR,m){WaN62hӜM ܽ段mc~~.;ҍ@|lJDޭ-@*o`Dg`f0cVc t8[w^FK"t^oۗowq[ʮ8}g@lFrH{_b9/ѡP0l~]!hg 431ӤDQ=VUΜ4^xIt;dwuHXt!_H?vF" DEVH:A|!>`Q3 \(HaѲD¨:h֫&[:?JvGd-Z+8j&SѬTEae1-yަGzĻ-dN*Y,eCgsObk0ӶvMv>2#:藘n!ی=DqwCI!o$d(-ONq~ |@DWJɕI!]>;[o M$Iמdx,IJ8˙ Սʦ*}j@G. O}&yk5y`ODA_IQAs# ]>.u(5W ^f%"H &ϙAox7:>$huSiFy54ɘ/˚oN{?a`C"JҀR@?OV6!B9F\hgØtt{4-.;6cڱ_|:Yvf>|;_sl5'7QwTҌI$h:Nsb4m*n#*Met"MT{qtBua0:cՙd./ێM_ DAכůgTۇN"iX"5hϏ`oF mCWRH>o VHyNp3l!$_I<|CX#@<ܳ1/(Җ{-څhUGхM#Bo˶ ?|`phlF̗C'9"&7g9>Ewi_@~_. ܲfsPVrcDRE*0Q;4 )@Iݷ(^9Cֶu*ӻKQ;om~{l-%Qe>õI {Q^;'p &~i؞IF P&xܯ=A7P'qm]sC ?$}F7S;|WJch6HزN0γ8ڻI:]h\)@`_E$'al-tN*s^8M+Dj.Rh&tA@_ꌡѡk Qjbqġo W .nTuuuvaՠQwcfH(,CY Xm ݈p4̓Ln^M$qecVSgV`"࡮kպQ%"@o'@sH́Rvb^1co6PKN= k$ى{o==5)$O [ {L:heyVZy}څ :Yʖ0+\n\M*ni[, K ǡ,nSٚ^ MەUgW^p }&d鳄p&aYӡF+?|_w_߿<w^N&|aǽG_hf|R\~)r|R7jrk\{{'k2}[,j]J7 Q a)9`ןrϗO:l|t>T/4d}f|vC?s~|YNx}MF>㷆mSb|q%jGPi*S%CC끗j"TUԅ@Z/X6 mxɁ.1#;A}GW[3_[wjFFy$ϓ\I?'[I4v}J o'~u$c FJӺ t| {y}RQ;N|aVzeTZ2{'S@kx >N Y"l;EIKg7%?I}d파zE2FjOL$/e|ɻfaDe_L_KE_ .KTj'jl6q_Dꁊʷm}KD*sβJ{M':W.Ӟe&WOX; †{!D,$] iCbe +I$8q͛R1`6km? /=CԴ8(\~ 3kh̓*6I9]C^nƴ^+< ,, >L9k Γ{0қG,! :Vi|G]fjTxei!@bFh8{XK襌24y7ja,EhCx7;(R+HEB;*O=Q_ X3'iL@LzH d%g2*s̄F|-%L}(s%߾t~.m|җΛBE=`&ݱ!5A@O$V<0"쀍[HtxuU>_yVF:VW==HSf'BLTiRud~g2cNxV]j5~&ʿH^z﬷˫hĖ̳gVsi81۲d*Acl|5ľ< U2blAt!x:=ZG@((A@f⧜f:j=%<?YyKa F2/ JN6*3\znc:G?z+:UMMU;vݠFQ[€)kͻa=Uwy`l= xI2j@D?;,WJ {Qn *vM_A<t=nhmY)T,O> |Dar!xM&d:dc4fIgA̩V݊Q)[}_VeDd:yta{Fs*j`&@r}熪8Y ޡAE{N@n~OXfZ'K ~-/yPW| fR73o%̈́}CPaXY\͌Q]|hX毴 R3!$ց)`oQJ\j@08 O/CNr±6 GM %>ذj3[JGF(>?ڳ ݄^VUDm;np`;,/+szgJW<+kzb\%)Wi9F_ߩm-Ba+ ҃-soto8ؐsΰUQ [8 Tiզ S:~w&R{(][ liKZIar~3a)rXf >v8M(jMFJws˩QOli\C0^TܼpA '{Q!g(z-K6J4Mټ\L@#Y9*(^3R]W`j 5> 17] z-pGڵW€(KJ jm+ǘo5G=dr_{//c7$BA k7u׳Op.43'VCw(gJxAh%Kd;)hfk9j1+;xBӇ3#+ "^F:j &yUNU "ddXw5.(6LLn)扄 :o}."%0hC{ٚ5uc =F[w^.?y<QXdzVP-JZ&([+Y a:nǛ8 cZul#[G밹aahrwE--*݂m4*+l$ow[Pz\LB7uWm}\cЂz%d˦%'m'"m\\qn15t;Ӡ|k7& +" nإX6о>"d[4nTi"Fa^Q=tUZ%XCNgr|c.*e4(k>vwf[VuL1o|T";hS"EĕR& Yn)~#S~[ 8~:Lc2gfaBXvrGg %Ef%u ik'}^`NۑN'&L,eil;U\a۩.*/0OkWb& -uETcb~{*|J@cՋ2K>?Anyd@Ε P SDxN耓;(ЄF0 Xx[2h%*,{ۇ)OMS#P:|E L%U N'T Ĺ*K,(M#SIȲ كy̋8}$r zeY-q-fos^2+I-~gY:.= :<" {J SYqpJRs, ;'=xl;x2vr6A{lubsO۲%/VԳ$- Cm#kMt.qnpޒ xt҈q Giwڿs:=0%ǧGQ6 D_+3 63Ri-tk@ J(&5A=ß= U~P̻9TAMA0'1"iϰ])sJ;j%·oooT kfde.fVҭfr'6]A OgXLʹ\ hʵ!q _kS35 #=CuCJg(+(2D~#uх^t=ʗ75 rS[o흄M} Y)yU"Z1y"}bpB㓜 z& u&3Ct4XK2:vԻJk 'LڟQb("a#sړ2wjQLzLJT(k.=u0s!O0 l iWu6P>;-jڼUgnѬm".Z|ضN7X)tӮ|.?4蚧p ܓ(XI^vv1>uaԟQ,x}?pP^H?ǿѧI$HTPB |\XVPEc, XZ$N3p00qIaj,XVYR33ѷyjEfnApFSRg\`TYn}E?J0@F1Уy^oFYZ8PG^'VKa0o\W+~ X+&_<<"p]DA{H%֏{KMx;_l6<ū(cۊ ~f]$?t'@>E Ybfr9CvJi V 9S[J| [٫#w8{2Tх] ւ@fInN`o9L_7ҝO`w8zU{pNQ~v|AkgO[m) L89phBa0tŪMvl-6vO85CrCk2N|shAMlҝu[+V¦Me/=A  CO+[^ʰ`:'eC?tR/T}35DװV?ȮzSp:CR^RPL&_1[ͤ[E3)֚gK!\WIX&V%:ދb?S5Gcy2t0b1\ zxZެG?a`&@A{d=wzkª|%}6+KLjB4Y/`]6]cn_)\ P5etHUkj.mrlԘmdo-I}Tn`nFql_z 贬h |i?,f:՜2h.GA&RùF;28TH<D;G$[L]/jחumUOggmkGYSk.eRvzcY584zlO1AFJ%:-'vW5GȨ渇V#/zwo@/RFzbpw4;<䢚ݒ&%1t{d d3i{V%Ap=K5r54Y^+o=;M] ]s7{tmI cseыy|DG]cӣtc/]*Iv:qxE^#1,QhNBO%eãmg糂S7pIpL*y[[ȯM9"='<ũ2 6H{ E>0ˁ} |lgWa9t}L!һ8Ou": =Cz F0~)=sa/U*8BDRSKbT4'*!.є[% m#  =J0A@F Tq1Ӱ_uqgJ yRRd|b^dDDmVr\Ǫu bXY.FA >z#:&$Vau2plGONj㧚biÎCfuqF B"[:56kCx ^)fa} _ɱ99AIŔ{d#ipRFz\,S̩! 'Y8 ="đ!;T(VAN:FM64Mނ9cNl+Ϛj7e: [Hsg\loH 0 13k绝V\k#ՕASly8.Jf\+,8XU)gY܀njRKk< ` *SI,{w DT)XWŖӀT#Ts4g=DMefM.{ T7-)>#9i4J4\Lys?4L{"3EEVVil͡6e@H;xBlb.g1[qZ)?y04KtxMJUFڛr\8^ Y]%BcȚΞkib 'OuN1ObP’m`ZY6wȀbBDGY@M ye> i52(rf#Ep k &䪩* *p} کչE3L^&H4'\)Jv,5Opٖ2\vIN(-Ӄ."!'ui9B3^Y Mu(ب9@cf0S# [w^_%HloZ[ (F%h Yg.V>%lX{xxEV2^} h,yXz/=x4!\24֘D@˷hhS)l mUjJ8}JǷ)lب da|=ie[qߋ2zBO')oy!vwf{)Z6虗OsaťjΞJ\-@ggig+UG[~)aH o|?,f _ Kqz*=dIp_r/[4n7SeZ?ãP(7:F;ך6jEwn5|-TUc;$!wSNT ׁP#O0PX^1jy]~Mhu쇇O97R?H *cE`6!sW-kc xzfH2 InMU2&)-R`&sy6O{9m d/%.W XpmU3# Wչ\8 LwOG}xkőA@,>0<,`Opc# e"VR" ʌ&YOd8H +LOc vq^q'AϹ.9LrMaU07H-C%sYqq~;WE"J ˡnnbv>-]j<0)!U&H8 E BU ,J'* F8:D6"_eE@k2R7;XyscZqQ |&Zê&/ yw3}B*[@/[cr1'㪋 r鱏ﴭv۲lP: [oL 1emϳBqtf<,:60w^dbU$^So-`uRnٚ8yZRXr7%A% -^ia^G:r݁MP.X*ⷂ7~/2PTzQBhRp|\ז num'`OaDuGf"!׊$Sl0BSKto:?yo^c6#yϲ(=sUyt1譨zb%'#y) &\l)˔#-1Zݘr^DphJ)r=6iW5HC(B ؞V\WX<$1iLe"4%R :n|*?5Du˄nvH.-Hˮͭ6!_BYq݆=ƀA{51@ 6.ѽR+qGNjq(}] ִi"DTf#A qV}vu9.n4ݰUpL$Ǘ9\NanuˣOent`r{!=/R!fe3? Tq R:&ͭc?0$6f;bԬ+)X"Ăy F nW2lo;bM)}T,^:qS߅R]tʝVq1\H$<i}~-iFtm:vE7uHQScԄ.y4t}O`K_{OK >Q!=aZzZkG{\dZi ,tvIy<J"5 K2*7ar XJ0 .jT:Ijq¡Rn-a'oV,a|@_ [xUFAJT@+uHM&T1JmlSJoc%%Qna^T6rc@59N*bur D0)A ,ר A0#)t6čJnA~r 3z*܀R3mQkVl.%uhlP\Xn<6vvR߿Kآ.Fi^Q_).~x%i"$  u 2 {kO7st1˄ppMOq k,bN]wi^ѣt2UqL|mgeTW î^|j: S.VO]l8_ZC{k[NA0q&.w(!xAi|˲",хNg[ Y?72\Pѝ\WO],WGqG~2rQ+ !)DEP nLȹ.Dǜ,Q7=iºW׾KkT?Cm\H'Fi ,Z}O-D.x / #W$8N? |z778U̦*O?ӡnwS֫qyA,YW˻o?9HFC*ķʙ\i^})xIW(M ʹvț?+*sisavW|mtVqN|=֥ƺ1~,7aWH4@*[եCUK |9vlߗ߻;ά Vj" hu0yz *Z)59DMExL{FczWܾ՟^P9!+&ŚK6-LLNa}C_pOQ빼YbԀ T m/qB#`]/"4X~{%y TZ6kIt]ٷm?L^Nlnhsvu"!'}7G%UGGNs d,4)/:h9aM[yuY\ AM'&.^SY&+313 Lt4.&=#|EQoq4c%)Ae߇|w݈|D7Ž{PKt=D40 u%flot/examples/axes-time-zones/tz/asiaUT .US.USux [{sI:9n%yH/m=BLlxjt1?2iIck'w%/ߗK1DLu~Hs%$ԾB*#PzU d"뚍FԼ#1Y~γX;01QE<$X(%Bf:S? =kaooYJSWgf+ݣ@@L&SGd-f*?d315H2V8Yji>B\,LũFlx >2žb^(DJ؀7Y@6:$l.F 6an\ (%dAN&~ba:g1>g$#qH\ ~hA"J^r%V8\B1+_Ei4ǴXc)I)In"F)Xq F\YMvX0Q{/FŊG!L &=!pp9ű%bmU$g3D9V?}Ljb% 㕆fD&UA5?m%g~s@RhGM63*ju*&i$~te2פ@|s.$@t ~"_%$Gb#ĩr&c)wU1!^T{8 W!ρf4"ԓXkG8%rdK%HChCnj"6X{8Y%*^JE+liShNo:KQ9R1B?r*>w}$VwVŋ[ؿ C"*S"GxVOP25Nږ0V.=`壣cXݚT蛅/+4"H{CǍ F@&d{bfl8l\&T!qˉ?obxC0_5 QƊ2x[rx_F&ēLZɗܓ]$QfDẼJf닜lkm;$gYAa~:CZDkb|u~^~0_\H~p9 =I"ȴ]QPKoT86QݱZ/TD/m\) ;dS{x2w@F= ˘H9*"ZQ,NXǂa5K`)-/%XJW_1U̖px9"I9Czdp @GIT B)X~{#סʵF{& Y M.sZGpV+@}$mq99'vŎKbr4Dwݣtv ǜmL$Dz SϫA] 2.J"M ,$U@ \`-Fc`ƙ XŻ5oFzd4kfk0}@TR|S䗑8Wѫ5M8f Qnxe7ʵH,.> rɿ˘3l)?Ut#jU_QRBTQQG&~ gd>Ιmk!Z2W#xYX'-ܴNxQ˳P#/-A6%ΑjqǮio羙m˭&cmٍVD9K*Nd *&;0Zr\fŒuNQbz)tqVSwRMszZP@G}2>/M$XbzA^d)3Dfws=TQZ~+P~@Cdt̩f2С(;ȥB9ꉜR?+qKDy,yFBj{Ʌ9jYT:h@%+=:-Kc=PѱV_ڊF!lۜo wHjp)›ȍI$P*2>XM)rFԳ'O ԁwvw~ M[ȟбmFC* @g~2DGmj]$] #FJg$dLfT*J(/ef@9+:?%5Ҭ 'yN}8Ҩ GM N>IV9wbŦ?SV32UM6 \`#G4Qg61'* 9%Ɣ}si3tdVU^:XR8;^b4QJqJO@^9^~SS^F#i$4SnU[,}JB`(pŅvXH$!ÃI@)SSm 53jLjtFG϶<׬5ۏ>lDZ΁=v||dYd=4yRpR^~OQr<,|ٚ!./.K` T\mRK=Ҹ~/leIfMTJuHB4RD6Rd]c-z)T\;guQ?ގOv&[oWސcZAuÇ^- NJ{|#]iyMuhq~si7;1m"h1(曩W>|mɽ1C ,^ȢֱpÑCxy6b[ ;;gSFY:Vg7٘EUŨ..{ 'F#zzo}q+ չ0>_ ]b~_> (5ÿqgȭYSv@k7: l)YX2OzS6lUu h ^jz Or舗J<١рH#Y*RSI$Z~6 'amK4 vk,$46eÛ^HdtuG4Ou9-KΉiD7maqHF+e=sM CwqSfo$-fŐsඏXO|-Lzg^0X0pk4 ')Xwߐ8#.9/"m2\i3r)#@C=%9"Gb R3ʴ+9ziB"$?xSta;1 5 dS|/F-XE:6J+H±fZr TO~ثĄlvD\AaFoHz},%*&mC#&Э1&IͥCJr=l&U{ѣ$pi,ѷŦt hn"z. pHHzZ!5|Otisg,7w;3M:-%,=(o@:^(lh7oqFM#,b|٪4q K_H RӠtEX33E翬f;g/Y)$!쿳_N*/ə/fs0_ެBd:ƀ|'8 T4L1ѯ'<l16r;y;p:v7f4lhud  4+ukj]BmjaIRa46^1{Ceb6x?t_B!a"ɔ795& KZ8gl2vM& 1]IHFTuW",۝\)5$1tNJńsJ:JG~DJii$t]$ V93v)3x}ki0W du'f&*凕UD׫z+^IR7.hQ,cn:Wr^&+OKSَY#̞#L5S*cXT-cv!|3#%)$^&\HzJt˞%彲~oV|yNKO\fjg~0h EKZltMb+N X.!PC H} 1#Qla[֩M iP$*ҟ'ǮƮ3/48"&$/- 36f)t{4R&g$2 5E^:$8\=':gMh9 b.IE4䎑aم`Uiz2ּ} h -ڳOSf 2h̡h5z:ie0 ZK|*5\fwIEKcdtth* Bw ,]rnMY&s 3с48%,g +1tVsh-5[a0 ^ϤrM9ةP_<5Âpͣ8_x4,͞gIc_&h4R1Z# Y>AULsքr(+]WBˡCڨMǢVI\rPqz|Ʈ3Wm8F3pO)I&I7jC$:T`nt!i9B gYX=įqvK6^Ll<9jY8?դAg1ЁoaA'Q׭A1~O0E,{:fb4wv hlW."`K@KDdBI]x!7WB԰@nҁs'uX5v`]aX^y? R@/v|OțF+aCjxaY˽ؘAUcpۄN487XM%z 2Wg{cj`՝q +n11Yc4IBh8_/ ƤcoWhy!|ۻ=HgɬnZ]`Iv3 {IZ ]#-_^ [~vҘBpeO @Wx/!0m>IS*V M;Ld(ՂN%]z[L\Qwd$ǽ ʽ۫ӵaÜs2_A_%A$fbplO݁j1J E'[4pX' P:n>L5pi آ8?7Xn|ӗq*p}`!LeByIq-ywriv: 9!VvZBΚN*Mvtx2gOԿ@t$[.&lFzL 9x8'^-vkngh%d\1 6rzFa3-c Fȴ/\.Jfʁ JКO:9I3MFQ4 Q5 #03{CE˹ЇgEl(1+ ߿냫!:^NO}RҼ2K*w*.1*c+J1IZ3|m|#oqB۟Ǥusl|Ѫ]Eꋮpgrhۇo9Uogͷf~ o7.L~ɾf6/ bsǮS4_wb}m;.gKٷZ̷A] 0f6|ɾkU6]1w[Gqz6 ݳKgf_gmb}-WFt6#]0|O/[Cek|}ГuQ{;xזF.}v]!e3>%Lk#$rU9$GJX(݁UQy4|y[kUvc 2)l> 7b,(kn9>?CZU`\j-Yو-2Ze7ItZz T3ćB+:Q nfޤM)hVuu(Ҟz1zR1wcP+)c0蔾HtV.ثJ#FX@u&kk1hfѭxo͵wkFi_Ք~@9'0wfٮdİBCx1mtHv( G"x쿃{;;wj_lRvG,3^l7de6y,<!'fku48+NIZ]&&߮]ojO#{}0Dсhet<E[S14Wg#YUw"{V-Ɋ)q9c\ \ІWuʷ&$jE#‚Q3T{wS1kYm`#L=ۓevlH pm0W  gl puᗢi3_:7Rrs6ܪߦ/o;\]N|]{y[a-Kfu^ϿWKw7SJYr^3jQ]Pg2,r3Gݴ,=7{vqs׭`_}\o~{ͣs< kbr/7K^Z=rmDB f@IK'f%rF*xܷt2ߝ#6M3΂aBisWg-Kn58("ˇH{rqC,:З}N,Eq_Dl>ujj8б4s`aR@{I%xV6mhz.Ygeͫ;%5r]fjĴBnםKVNŨ{蘶0*g#ޣKG#=v"ipN1+ 8s-W 2G߯UC).m+^Ҕy_P].߬lKrÒmǶn{.O ԜW@rh8~Xhm vm3fRqif#Q7$e.&є„f}{s3Ԉ,LE4yl2BisAe>Q.;#@pZo{'gg_؆\UsqOIY.ފÔ%!{1 D@has99E4* D Fs_}xJ1~R2[;ƨg08<)$N5 IW4G-O,|;彗F^yr:m +kPUVᮾ'F7^#fk/$a4;7(fE-d~ӌGlEb!^]!3Ᏻ$e `R`0<)AЭV/Ðu c)Ll[o~$=N+-ba Ѷ@6OrфmZ"a.e6@O& 3lmY(\θǐRF< Ii!Pˍ8!YjCG0,c[n&5oOriqYDj$;cx*&ǎnQdOr\nc#W cT[q>%BtfIr -\MiCpóy,Ҕqb 9X+{C* " VyP@ךhM-N`Pǣ^)nr] 3 ?/u_km;qk~֗i6)y̰<3Gz~Oa J}鹁nASO5?]v6b;f=#u9BaYU} y2Ɂœe+5[|!qR/I\Dcڹb[i=Q! kU4i}+46@2{""7nߣzd24g\BMu- ,b#[œ4Io݃wԂ&^ypZ+ZGof )뒪!H-XϒPT-Rf #(:6t4uld%T ң*_8qs;\/HKl ;,HM.5]ˀ?WҤBb% q\&Rr&Jکt /H)DPxĀp y eHkqe=SxD}cYaYG*0M9smDg!\0֤[HnPLݒ˱M G5oG?U9֭u@2.8+ "yMxjsmiEibG+Vf ^YS uM 'I/xNLWₚ1+)6#v ?$ cc b,A[ .h`S ]pn6KrJO^p o7e`~_Α;k82 ~F ű3A 'ba:m"Q2}*CΚI,]ՐF10m&RWB5 >3⁶[٥*UE8 plyz -ttbD} 0Ơ|g8Lo2hxmn:!32YdIHy+_._; N4!<՜qCf\7́/3#X ^FQ]wGQ-8^&Vpmp?W,5n0RXBRU|2mvn28HHW4\8EҨi¬4;=;F/VgslLith`j΄,6c.A 7hw`xiZ@75 ew;9uյ1j _;U53f2I4D{3 7fuovYIc#fPTs~>'t<, K֛uO bW{Eos'Ac+ߛ`$Tr 9-s$ ?rn1-8dMvf46)bao))1jRՄz\e |K\pȭx_0 ɞ6h*oYqRt\uҚI<0_ģ9v~!ҽB_?"!^E33Ae>{YD{+Sy?%XYV~+ !߅ރd(Mh> %FP UX :T|iAf"nIfF!쭷 =),=D:bCr JbnL`1۴EmVf.UjeLCD:fAuC4u4.I֐Xcta3܆գ??Zwmut}b̷jt ct=G56:w T w =NEbq*[GwSTctcpنFj=NEpZ~]pqS5:.~1:۰8DEc: :.,;t|e>=~*b?!3wa|@>QSNdM41*ݺTglkU:"h6=aKBghN뗤zeO-G4\ Q}z!z"zc^F1z1X[S%zVnEQs65|݆? ƣДYՌjk3c;㚏bL%$\wI۪.-ǞtҚѤ,&'Buk#DMMx\tB-Qgw`ek*z-,)+=llGX 5_Cm֖ $>:%0KŜx"Z\?_ Me0]o/!GԀ[I`G]C Ipq-o@cX!ֹ2ol= 9E`tޏM5 J=䰹K /4Gh80v:W4%Oa]vMw zB/dqMaZ)5^i䔐`E,DgtV1/gKƳdaffo,\`9ؚ_Nܐ$XnSyMb~Bo{Hd3@Pc+O4c ˒d7;b̾ydMbR#9 !6TDZH1㠖C=mMl.Û!uws`0Rj^xUن|"qxq_i6j\aQFQZԴ2٠va{i%J7v U[|yT=rϟWąm°7w# N}p5d.hVnGoTt#??l;KSb_hM!U']ltM]Ŭ,.5 GHlY#W9^/:LNP*|wH>IH(/3=°d([`'MRsЃVV^0&eW 2J؆Ie=14HH@J%:$[v8K~6Ʋ@ŴvMBrT,>(*X%DŽa;A ֑ *ޕү? 6gl_^7\LeH(6f!u$WN/rZC.;=@ּ3$){DaOHA ěLY=c`@&\畴 MXM-CJaoH=|%бqb_"< tUpt?\/`6rG;TvmL6fsyw Qr ,j6A](ܷH)puu jЏWaJzdәf #'w1ЕtxIF} *>+~YbS>m1QdsԅXy,:NkC<Ɵ֣i9ZL&A\ z.Kmie_PeIfk3}Ӱ J\;M6-\+Wh]H'Nk 5Eb65[~c"¬fU5-i `qM!ZCTk?ز +GiѦ7B0 :8w6I骝 v"!8դ^7_'PUi#Y.dx!JQ5{&s@xڝs f.¬MXMf ؓVo? ɵնsfs|)GH`JqDJE`]'Ivkw|@94ƈI,BP{O"r:M"cɍY|`$ĞA?1Nc îH;% 9&5%K%LQČCggnhp =Bw`4IJo?kG)uq>De((-/c8g#Majfj޹6ݵ65sVĖb k(cf1M,L䁀! sa.Vh^?Lhf+ 7Oe߉T211^cNC11AV8#]N.=}:,W "&?dz7B{p)dk(ZzωG;\"隢M\FOnu3el\+pF't‚HH&bdSWNrǔsqd3ښϹnx24֭.2ҞɒoooS幔#'ϟIlV%*X(&ThdXB"J"XS% I8eZ4&y#.w[E0sy|Wrk@B,M. [zw5FCvmբiWyI׹,^i._S o&lk#}ywָc.6NZ51Qi0AP=s%GGf*髻3gi+Vۨ$#'V-FJ v #u7~h:Eχʨ༯/w[(Gb^ܐ4Nn{dse~j-Į 5U™vRGBaIA$]/׫x^s WN Tu:HF QbH]?/GU55u?p'n5yd@P~rVla+]NK~줆rp  A*r7"1574rUyVc. VYy@M`GMpr M<ŗ#Y1T7@;2$4m3?KpO}ո$l"ϿCuգ\-ី*+^_dG5 6V.sll,3 =[M&=A b *Jӟu.4OZcC)v`ݑ!`]ʚ&"D'Y ·񚦸.sl68^d@ȅ&ЉJ Mrf Q{~.z.j*HCԏ!qY?18sf瘻{)s:7s+#@_"OsqwSic¶2r+=cA#[[ʯ:OҚd,t/O"Kl~h9l;k`> N N''n_Ԕuob=ӯ(ɠ6];>nIvm_~Ղ*M՛^@*aH"HO?WG7͊]UNVyr۪SU'Z\G:/g88I!{IBPNxg<+WFBd5j:謑߷pfZm#Vܶ ޹3Mmm9z-qi8)?}?S1l߹]'AHmn|pT m$zB6mYqdܶF?]ydf'meQ\zqxq?xM4&s?|l"Tl90C 3VsW&ɜ-&^߸OW6 1 $I q8OGp0 )-U{ ⷄcx*/ylӷ FIY^z-TI|]VW!|jDFǴ.CO@,G+ё}ݣJZ=DǷ]-,tP۱,5u8^=$e{b?C F=1Le g]GtR;}bc2>|ܸGٗRԤ' X<'VguQĤ$\:`n/+qr&-jq,Ph6#=#nPj_3xk5j׋p| h&&Pt8t`-v2RbR& 9h-zOJkRc0)8sRv%0NRo3d8hsv p`T?z%μ'ûא# خP{abcKmm⌃dp~TGy4xͧ=DAe+hi ߘka]ԫ/Cg_'5,L@)QϞpmoV| BdLVo Thqccv*J, n6|PN{G) ?#$[=$eg$|e9d ߈&HfMG@90BNS"-}\~Q?X4oT Rst`P^xkGGlbIVO*yQA's^]3}p5@Y(@|Ixo?y&COҟN]9?Q+ݽf0`Nb1`N>6B֢ݏ[8k.'[=`yȺrY[ ]NÜg\d<"LI(CY[ٯ3`pg([inj:BiY\A֮x9{~QŰp_orܘF4Z5ҫ0i4;X"ΐ.|\)__-^4OoVjATˮ):{/w_I4pCin9=zPK;tW37C뼵'W!دZW6Yu9Iڵ[+^i_RxR' YM3Sh[ p0tN8wkq6—{`f $:B;uYS\㒷ؼ E|tlD৤}L~(~tgμp$ULX=udXA {q.zM}%491dl5JCcx=BG5 lxRކSzH@ג⢃j %dIx̤No!աjPxS 7DΝb(z{AlT:?Ƌ+[is^&\5L:.L6Q#e:d;UK6Nw.BTAq҉V(MaAO!2ïhf)'aKh{K[BLPYae5V !iqh >Hi5]ᙣ 㚒(r( X'w7I[LlwSmy:"zFx;IlSܔňs 3&b`~$* i{\1=Ytlt0>W 1f& |f "{DkSs8 Z_bK;bs2_: ],}r@7g(S+$3&6TuYCMHl$x!ÇgtľLSʃQ$}fQ?u6g1n6_ IE jLjZB~Fç;E$LFGV`o5 ʠ]\4#/lGkd)DBmߗ<\:UBPMH)&y=;=HxY 9Y]ĆgA+rl- ָ4>>D'Zx[sd},^ (ɜRÀ?B2zLP襍T@ xnaœ:&m|?9G}Aq1`oH5ӌ))9 H?7p,ٜ9J^ 0V Pr,]Vǫ:M \cQG`)Kas fv䓜z|C$Y\n<'TaY`o;dl2dW`b9:-սnɳPAϢI}8 ^ӄ0GB-hJC]hBVT%͖r.=hQsErj]v&NQ3U]p\Ƃ ):P79 $#հYɬ+8({{t3ME Ϯ?d.Tb6NVy|%8;9'dE텲 mBw!ۏDXM.f@%-$zD;p{" k!ËFFYeoP " `<

AKK( VhJ'9'""=Nb.Eت;"b>?m.gX/!#=X&sňI|I"(6#)֢a)tQGޔIN[Ɯܪy 0 GFݪ )FfvYC`N=;z^SDa.|J` ^H XGe@jȤP'q'&kR;XЖXO(`d9Sqp_0M @3$s+F"IVrj Kb;XC׆b`T'30o{29̍΅1[2uz}^`1[cGe.lK@ 9GlQ2ص(sZHsG[_&q-l!4y.I&)`GUf 苨7^,fp l~r?YȔ/9-;%wҥV| D`Tkh/B-䡸kmv?h1AA*<{J(ȬY,'s { }tpV͖r1)#`߫o\HLN楛wHT/''4wHdywfOho%w )ke:!5F-o$ 7|p" w?b'D^{־ٌ 2z7 8OE,7|oK0=y-(K }RDWITb#J-.h;d\gD_#?wω\pK콹=Ia·l+рEշס5_ɭ36$\ C-$^abגOu9L`Kjz%bkqP@i`[o,sh^AE?l]I!f0:(׉4Pd:Phu 8ㄓa<R3%b!q;3^6 +э"hr]Wkw;*=7ކBh$d /mrU1Y׌0\>G-&Jvobm,b}"KeѰkc9*b/aĤڝNcG uʳjPM,%Mq9pCa+OrjX4'!̬%H\I̋$. !PJS[DjYDʪW]tǶ2,_FvlH7W}%J2 W?NE.d ^:ÑbYT*؉R ȵ#mI\\)QI^wKg D96<Ic݉ntHuqn7fS~(E c\ CgQMMAWsh3?߳muLH]2r#K+ґC .qf21^_Pn}b"COP:sZؤv\DtF5%8D瓵˖Ib*\z ,w 3]I!@:pbF&kA#Bw8gL(Yk!}Ƶ@qy/'슉>u/in˦jrgn93 v|{K t3o)F#U-;ol'f#a̗a vrqO y4]N~ IۚkQ2hѬ˰w.gCY=K Jh.&բzuC@bB;#`F2fU8={],}!ĢcX_hJi}43ȵ5LJq PU`iYJ]WKZHSK:DʐX@2e-xTw+ȴKWCǃi!i8NSdIu>P@5D+bҌp}%/+ض'8;d]MgnT}@D곻5%=%1HCC5#B qw\pm!K@-㺎RweIh5OrѓNQ~ڈ;g`~ *~yE pH3Ei('H"yXхYG./2% lfٔ j9#y,.kqbMs '~xnoN\1ӓu߷_;=OW{ bzc0x|T50LLWx^zH+‰ŗJpȝ{ fsmzSYs_v]%J@8ж/3ɺ Nxgr#L,w%i_!ђspm,thfL@y^]j\d )HX1A=)&^a奨vzHt]hM?{F<#1  8IR=dz" <0=AaUD$iy~ci{=U1j%g/WOxB3WG\HhY[2) R Ap"8ҵo9Fٗ/d<"-T0G$NN_qyiIV]m0Z75>!ujI\Ԯ 5A^@t&3)6:NpdFᎁ" tYdxm0c^.^s6ĚmLӏe!5`RI,#ؖcC7h*mK/`9BGRRx1cSd^b:9yątRqaoE2Zy/:eGe5-$L6@ynS߮}m s]de3h^$񥩲 KOKrސI#Ɗ4jxԷyWq6b(?. A?rSB0^|is"LD ve(g7D.PQ!Νuz\tk'9 I@Mhg< 3]g5FֲzGWIW {R:9Zz13SL ֡f!>zPAHwoDP! 5aTlVW#;ScVby\: 5Cv῍ [p1Nۉ>PEåp-q:# wC.קk1ðkƠMYa K^  :3ARoMp'm`t u|)܃i`jyV6SI5mͭjF\-+z8u^:̯A7Ck2S +.V3z&nuVbĒc焠Y׼2ƀH4[kٝ;*JskĞncJVtQau- ɺ^gln8huŔV.JX̅YƋ t{fEv+;}Qo q.أoz9܍q¡D|L %^!9N%>.s*K;CEpK~ɦF5WpŽv ޞA` |TW6aI $UHQN}-UL&ukvXn1rH@Rce"&I*d# /Clm?)3I#ڤ,sWs/9GpWk@!L+ƺѡ܍)"J7~5 qN©C^#1NX >5V)]`VN]|H-0&%I^8S C,w(k,f.3(';R?Qb%qky{-:xs`Ʃ3-|ǦhBϲrU)\2=.l ջKV+_P!>U%YGsV ʸx;sW3#jo.E,fzKbqJ:ځ'u[-k[AAuAמ{%!:,ROI,(;`NrJ_̝_,eV6E \VwJ6M~/_* Tzj#/ݾ|;ANrǜ!'%2fVMxmS:4|o|Z+R'73MǒBQn(5#1V ʈONgsZ_%l"c-nj@)WASE>B rQT  ,S#e-91r':s sHÆ38[-0#GeqtOK6498p?˅seIYIFv_i<M"1[ng##+'Ȇv 2jP؆x>.I=kX^VfT}`Ng3˵TݎµlV)|syt/f͇ R}.1e 1 @> ً \ @q z@U y@V$YK զ)jo2b8\>=#Q*MAX1pU.^ >uO#?y$o4}1_O_~;pvM#|P7/gEm( i/.p".5"p,BirݮDۦ&5H%g`'M$Eiy6Qv{IU2U_ݴkCv%_J^օNuWS۔Pk2qiEuo]W~H|ˈf -Ih+{)b۸Dr\L{S*٥XN vK%^4Vv[Tzt{pG/^pz[_0:KxrY>RȴDtg lʗt0s\=ҩY&n(ٓHbTqUH*wG j+ <%OriӉep<7> "ݹpؽ<҇sq1{(o(H=zYI}yC'~J'p +5(@:p$qxigţbiԱ"e \Mz]&-kRJQ|T;[ݦ7 :reeyl_f]6 HJKU~ A~h'n; yz,eր[ ӟQ,!cvI4K^eʻLώOUnG8<{l7e/BV1uXzjM"gmmP5BMB:.dt{x|Ln %5MvC;OM2tQݲ]k%,QUI&?C&`.Qif"I"Rc U"MD4N4-i:߰4P 맦ݛ`uO?'o޾>??n Kv w.ɹdm mK"!srL䢱7d3?4 Gv̡F>ce)\0HW-qRcbl1@*eXEEקOJ(\ӝwN"U_Xs' f/ǫ K)qQH߼>7FB6ԢIqF]~S2y=`{o\r(DMїb4"@f/@m$h }z; f,??iDl? UXAJ ^Tk5(VB}2 U(Op-M'qz"6TegIZ5pkٽ}rH2H́'x(;tiWPٛs^qwL0;tnGݠ# P V4 d*C jc'4HSkUe'-P ̛ yy*a,iE:Y^,!L5 Iz񥭺IPSͲB;ς:2nT窉0hZFIb$[.r?RE>" 6CI+E";.}܊OXo$YfLFB7 MadL/GCpjWL7+>G%2Y݆|M9ny092ȸ&~'\sR7%F+݌C%_mNiA|͒ ~~uzj2Ҏ-6aWdvsn𰲿P[uKw-LCU_^oܯnn-ѽ=79ٞmUu/e+Ft-|Ńznlm8[Ys?.mm{>2h,e Wy AEA,w*[dh-/}PZt 4 |gy\KtScm\P^R,+MnupXs }f+@ 4cȊmi֬{R۶`m50fQ . ܽMdvzk&%5m)[,Zq1.d,r0BJ&`ɅPHYo^}A)ZG NÖI.Ĺ#!Kp (?P0HDo:1/';yXsY9=)`=2&wK6kKAo-6тS%Z G5xs6XL !+g!ౄY?nY?gc!hZ E3 8ߚ bcaLu Iyvft\FUq]2rAPjͥ5 Xaav}-FQ9B5C}6eiVU ڬXt]7{VƣN͖nKnO4z]v$,$#`Iʗ^'\:}4&uO/YEpk^pMWNẃ/cENj9 <ÞƟmDUXaps̩-,U| f|C]5,iH/&O'.H;aA,[FQ?@YUfo@e O$cM{? 5hh9DQ %jd$Is^:zמg/g6[M]lhP+;#&m2pP5)I}Bh+54&>M;;z{_R<>i:&~ZeeH{r5RVvDM䔌``&RHP'O1QkufE*ʙ8uZZ팯H{#"ׄ"OrHXneŲ_cJ H.nao.V0[ lTH3OZWP.J@&ܐ NW.Bg]Z.V+Nt,~4:b# XJ-dfyv)׻üW.upb+jNKY5ŚL)$g@JZcDK#i3]?K 0ˎr [s$ 5b'*ɒw6p|"ME8 Y2Q˳y rO { <wd!2\5$gz[n 42}!ԦsG:{2gv2P*jtA9(v)7"18hӲ~i~'7pLP8Tj?W n~_T^j QmpWifU&VD"i*O!-=ݏY9K0qM5fxȞ*[v2eH&#8լN,: Hm쳪IW⎕5S!p7ŗTz-/8My6ru]ޝ &9 VL+40a/D4jm}ݣ2ҮRD -YƖtYlw(Z@=Oqy1-qNJ)T:KA%x/O(Bl%02j[IOw%IK;t# /[ X+skgjd1B9NWv^!9?u~ֿA}j#;o&lc[G.HD _%8&wc`軎jiZ^{d{M훆"H;|90>[G?6HPxyGlnP QR"z>lGfϽ8&S06ۨJsg4WL˵|HmLqШG`pV;##pz Fަ*OnqLcOTh,ɱjqMoG*Zad<`_IA8:{UF,_/Gt~H ?pJNyM?"ci$‹i:"i~,S5_."{>eH%{'L_yvtZAnk})?Q~=0Gg)98SD* %Z|fSqYb0.E:*e@eu9GY8 )]=I7O J5nmUcH1}f[^%OI ؆j@MuS  _3|1}KkMaN+cxm Ը}xh Nh r!`iԌO<4e=2ipW<2a#HiW:!sA6slEM,q2Hk71X (O~'32ډ|B/CAoyDf~C0|@^[R!J?RstQ[J`n2B[J8Y?2`|^_.O}/.4HD!(-_Gxafgf\^ ؙ2 93d@vŗy$f^ N7{=l_YܾFe VQw-v/mձ2|46B p3]CplІ5}j :\4r4wq=J(74yGFgw7mXm !{Hq K'q"CޮYVʹztQf`~#=6C ] x eXk GS :H ĜQ,"$y|iR9}O|,X1Li!EgHWkiN'ؒzl[xx+zӨ6 Y34Mj-H |]赼=K@ 4@ 0S ɖXQM8=I \x2QJ$E.*#E-iFd}o' kG'\]n.: 1)x RϢ.@4ȏG܉e,*$ 'Пx̂?3::jX{P kH0Xw\STM[T"r7A*nĺ{o=صU %[<:G[vo!hs벎݁tIv3D 378izN@Kl>j͆Z}MԹ(r(HW~fxf1y֯!:iNpSqB6֒JL*" ci^|l/v vrny3p뫳۲n W ;Ew/Q;jwzcq3+d3' Ǔ1]}Б=`OD1]}h_緸ZuyF;`<܁N_`(XW`3lB$mi^M}$DP[kvnٍ>=ߐc\cr!t̿_+%t]^J`-:hTZ} RݪUuʺUW+SoWSZ)EMOoU*-VQҌY7KPF{sj]BN\ y64cW KW)!_ćdNuCMzD2*蔏I;CX L.DDQPS2 Mp"#,D Sy&!#ȉ'[^q)H>E4!MwtN/6v}xDE8g,r1H1ϟp!kp&1F0JZ9|2_hl/<<ʇiomghˎ*$"Dj:0Ly_ٍLXzY8ċv5?{m W E0KQf%/c.H&2p*#/9`3ǏٍCƗI82 <."6: "?|ÉLUB^8<#(72ABS𻺻j>bH8Cc= ,+ yL :sl/8ƽ-\ V/zvќO7 QV˘k5c EEAZ:Qy8Y+bG؇@RᒪV@(ӎW~Zs <G&?^UQ b#u1l~Ktv5wuv2߇x T_i! 7t\;Sah%4\3b0y2{ \{ JPiX#Bc4uwWy/c%VH^R LJcP;keTv`磷#X3|߀_HBcѼAFAy XB=z.An2IE DN\'*ћWG雵I0}H1 _J ښ1QN>% -Va-k?i~ 9+3atWRXNG%84)uc݆xƬ$ m U*Am5l]>,;(Uz1@0[$oPqІfڡp.ɆBv#Qz?l=j0\aP%F0dxa/Dl%MwO_b>Sv9$f\'̆WI4L)m:0s Ʌ X،FlcڹPpKwC5e ꬁ9O:"L:oJ6Eh\^Ծxnl@xJg`G,+эҡRsr+k_É즃8zݎu mL1f~X-GG:8hO])4)m EL]FBA~JQD"=ZU 0XEbawqNoj:!-!njyB$ţĚ1<>Gj|ڇiCg"]~@=L[8HTg>6I O?|nP ٳǺ&6ó]pGb.Pah 'Ӂ:G2֒g?G`<'/@!{|Zv r_V?(BQn! h7t쐆LsgX=-Ol!쓠ΦM}{/v;&oR';jƀs0d(]V)j6UsuZjdKV|x ˽4|̚ZOW-֘+@! f*I{zPx#8?dL􁶣ShHv (#@o9 §h $psW( H?8te. Tz'ͅ:QSEəpt}F1S %'Z'u˩I`1tl<:{JYX hWU^r)`R ׋&A qàD_ĻNLV6t&8s>7VrOj3.~Ziٯ(ba+³fyqUFv׮%tN]7goⷺHtBR*o)]@_ ~!W$ >BPm(u:/0X:]/`&@ d{kK]Wnl(yӦ-b.߭-}do XOznV$x[l1UWԶ5[رTtp5pu5״r y$}0l%; HR#YuCFbߨRi9Q'Y^jStD2ԤĵtխRN _= z; ѨxvZw,ܿZѬF+ MF(d D:){^=p^SN#Tjɨsl S17o'@iE˜<`5=On ݇8(fQ "cL47&hv+-boƑ<5&w ݿzֶ%Wh;c8ip96`Ccpx?y-@qG֪[Rwc;d2g}]U_1]6wZG483/":>UEWl}-_7g/NgӓǓɫ#}2iA*fM+sXy{°(QhE]Ds(|\ E-CYƞ-cۣʭ#c㓄&!]V;AlΖlc]: dC5;"dDWI!De6 L/~-f RȎ|O}αtm , RgdPX㓣;:xwq/dk ^_I~~rv?߽ z{rQ]2ag`|KOy]&S1)VSInG7G~uE#9\vO?mwDoy9-+18',6K{: R42R2LR/tZO)-HlkjrGkA*C*)mW!Q'PRټvU{j.3'4exZo']1g;"1 O/c"moدUƖYUX5zV(ΥR*TD"{,i M9eϻ)3"A4ՐrӼ~;gCo{-QC+U~{ f$k5e}k#r4~Ağ?>.ץ&ߨŎ^O])AMNO[&JTe<Ӕta=:V󑡬ېsamUΣ-'}U]і@7p:Ћ'Oe Hip{sRQj~rr77S5[9mDq}fsήb[maP/^'0lڲΝdc[w&Rp!A{&[KK JVfe^\(𦔱y}B2.fG&&ZKt=컴ťcm3frq$MDUb>/wccI`q?'J~t㚪T;>w[ghM|j` ɝl4׌1y'2aV9!Ta#A//c\33]GrFP<̚Ґ!׼=TK?CnyqpoG-|M$^̨@gmءtr5cJ|fVcQa,dQ5&_[33 yENZ=^_YS Շ~ 2Ǫi #X=^ݜA2Mod):]pԏ?9;Pu\y5#FD >% XPNM}?? ~ N ;-8[ EʠUsqg^_/ګ/1 -d%FK pҌJc0b3!שP/,غ"IGIȾRjr'$R M`:-!kϑ,i2 2R'hJx2pOouř~]g&/ʻp/$BTv:GVS&ajD[Uq:#Fxr53n0IYł4N$ݐ}99x{{;3mM$J+"3N8YPC!m(cc @vm8.|YQI]g?ga7Czq]OwW"7$FDǫvp QLf eGVSUCӻz\ے|9wy)EmuFDs9P߃mN(y'SnYwavGsZcr?D86!JϝJz1b$d@L¤gMڥ yZr3BbI]%cc;q\ʛyI}>jl3ffL/D|o@jF,xF(1%b q,lv}W&Q9 vtfKyr9c W_g}]\Z?F_q>L<%"4Z3^ @&A?zGH;9F%ixMd"I-LHpς:OKG}"JƵA bG4䣡62ivڇ7`NVk땗^Է?PYJ[^ruuآ#WXS0Pl;cx*EG3v8(R PI9g$8i088\@+ B uL rp2:ZϭbD`<퓼҄ύz#o;kzSȣ,aB\zNW6Oeڞ@_<ȲȘٰgq%D/&էaͫzQZxϿ.]rD4h:9X&bmWVe7U0O%l,o, w-nj!ow Cev>8]yB2%W'?ndjƜ[n?zaQ+x4RH~Vtip6¨k[Dxϫ^]!#2\FxOG˲ _ !x% *h%E[@*a=AՁ$h,No+=ʋQ0 i Q? E򒂋|&xF}%,<>M<<2P 0*#QؽZ$G(/tø]ǤTW_6q8.5/^0mmYKc?6EφY:Ӗ">R?ӹa_+kVP 'z\k 9j$,>)Y/e8S1;@ >P5x(O&rIOg+'n9CKƍ 03P󼌈oUbYj݇#pb;gnMǬm›<59PMD;(?d(1gT /τ ea S![ 06x}A}4md $R ~ux,,9RT$w[NA%ƗC p^a.a YS#Y`LlF#ur~0MPl(TuPW 4/\yQ)ALc+=@nv'U5ڱ?6 *%5KЖTpH^}ͣp+=Y$6ՍD!><`g"[eɵ$Q1K` X9i DiG:*JvzZBvKƱ'{&ShqeZL}a|k@iEDfw1vRWִ0:TїpZMk1 gB+]9N( ǃps23 -C(X2BptCsh?&2!%L8P e,v;t y-,o}nGS)SV % gUՇZ(g"xvb/0notx,5Z^/M-֯71Mm{*AA(MKʣ~  UE:- $("92*^]\Ї_v9 FVci]}iA"Ԃ261؞  TO^bNt~j*S*.:M)jX7`3)wfʽ~%@3n UnU-E^,>f! ,Xf 3TQS#<o7"TF '@jnS3.H.IjL SVؐbH$.NE52dRw`Y tm䵍`e0{"s}W%D&-=E `X"o(xp[NB-.qBd/t|R0r*m/*@D32*U].7C9@jCXcrv(of%UFZeӥrDy"L(cAu+ƺ_'|+=0.67 l"ߐN5D>=O`\?Bf:?dgot٠vU8`P9 KO?Vӯִ1:F)im5?NYFc*\P &yp`7jkQRE\h٦ևu\[BOK]^ oeA@$=#X[NTm8 dza'}U"P" G5bJ6fRSmJ ͥ1^rJ\n_pcF-wMO5T4SVG)'LvZ:O;azVeA5`|(^xvHq܎F%&&GM"l6exm04іHÃZ9Gl~4X*F .`Љfإ^ow]LT,nv&fokɕ$~W/4!w6 <)#a-̙'$tҳjx<O%niB\g~ p!H\FVQ]RM Gd2kKm2r5l/q[M>8α'%>*QJ:kԭE獑"[i}ZOiNFm7Fq芥lx7j'/.>\"5ڔoʥ%=a܆dE<Ċ~UimEiog{GN;^5UoJN;}$lZsQFr(Dʐݭ]8wOQb'DZ%j *WwϑW}Ⱦ%CRԘ[Q;2|9IUuR%O{Œ6'+״[!w.?sR_A1 05쥼J4$m;&(+d˓UH]ZLVfb@=#32v(M%m x'I(<3,.tsJx̐Y[A(䐢W^M?D3tsȈd>|18P /#v ȡ_( G/m`:+ցz|[5;2Ĝ"bfUohY-nZ qu")xwtt45YxdױH\ H~~B ^h/]pv2 dRk% %Ď׊}}}WlQ=,GluWiUX\ lm&vXrn*GVk\hʿ_߆"/&4SW"-1Z|oNi9 CC}?ظ煹z6gdb=F f`.̫y2Rڢ蠞G LtHH]x2ZB^舉FSNXLv>.۝I.ħZHp7q|k!1_WɐÁtA ?Xf!uz7!1b%Uܹh(1P}AL]b;ꇛ3sb8ݽ~wkKl^o{Ey!w& (oIJjxGӾroh,G: !+Aa%bq# kmQ>swJ 챃/fT(_B)SxT5.;Id1<[HpK 3 zu}]JIe?lةģ{<0)S_̭^*J:?1B蠅 q1goW5 S|Ow8 fRt*iN;wh~bU2S*P`r F BB{323 wX%f-YsQQJn<Kjš"oā@T(no\tWV1@ *dYX]UjEWzf#:`=g,N|>9^K2#Q,o|7eֻL<Q9 :Rf09{Ymf.,5T,*Ja gw38U*V\'(k3&ҷU Yڢ&>Vj oJ}Hc:jJV.b0"t4L7Up>轎Fi?B1@נmhnQ7ڃgXX] D#95W%ƃ2 9[ioE hu|"VMmhP6QiH 9W| *hD,vUan$'Oxp9?}Ί.,(tq%-$%ĸßkFYrN}җX[t;-} T#sk'+ٶvOMBn'9̀7t"B@-$L$PVL7f@[c#\\AE9fBvXWplJu765jmu`ԛjLeN#fAx1W;*]2i6G *`CmV^(j;mޕKZr^p]]`VhB3!oߣ/ė0qj"&6ޘi9|1W šQ9`FzH*babL6*xh:P&zm4=22z T.U0_"oC9M8<>:9w`|8tWKd)5=]|Z/J&$G8)HPɴH]&HTggA &dk!\r%[e3^G(D>Zʢ ;ep 4C̩y##F ܯ5<ޟпEpu { >S4Œ>-nP-ygGՑg/?hQ:)!M40>BHɰ̠t/ /49u+iĿpo Sd%j Ԧ[!_QJ.0 X=Oes,x%bo&6E+dQKHE׍^r[1X_N._vv Bl1H1.Y(`2}Zwï0{v:LaM,ğ;nn},8ƽޯE kCE {}}vwwVڡuml5 È\HW`ΟN5NH&u%R=p} ]w9My$3f1M~z(`jfvZŠދ:]1w?TezENg%D{:Z~ V2GUS\ZHZTl$ZF Pzn͈̅\#T #~ea٭|x%?G0.R|=q;*$0E)1MM ]aq= ݐp. '>gWm]G;~;UtL򡫾Ӓu{k>eJ!PT Y4'X g!dj}6U<4xrQ1;eN#ߵLN=CJo߹x(eKE 4ɐeT@ (cبh+$$l:+>8WkmC*S-U ˟g/O|byx[Mp!g ^>~BA SNEߩ2S`( YЍ)Ү31?RV PK.:7i.ѼmڝOq՝Az3}^>s4^g&G8TMg.ⴔ?Nտ՘Wp쑞SGthOs(c %2f~AI!?#%q7MNǏr4 ci ƹ9?h܄VD#\] oM-^5mWS+jGP;%PZ$H8 sJ LթV*| lUkl*}Yi0%oz&}V]uݩXPu5~(ю;'D\'C3w-#N{m@0®5ߪy=T`6jeb/O򊝠ƍk:ZM.b e[jM ^9=k/Vʋ+CN:B8 ȟo:)+IV*m8Ss}?gc@;FY#D@?4IYs7♢=ԁ"HE_#7Co)d靤_f_2:o҃p6r` `fY(|` 'YS#R>\x a)Lpv|b*ft!JF+,I?1~7Fyo˿VUK2i 4*waPPr[ɥ:7sgNrv7KԞCBs9oN]8HN5W9~%k^^#CZ[\ˊ7gނ1kvU SmR[=n;ˠ6+Xbmicʄ^ "^?wo˶ eN|a۾``z#v;_i@yW` 4*̤RT+kR NvCfEQV ua86r '&PW4ʯۤ.·ξ0SwT7؄XM}&s c]aG2S)B]E.ejwqOOyREuU8X%,"9m^w %pI~s[r!*Wu>f7?nj襆V77WX.&A*N)S;˩O|SDW 4V WsKVIP8c`O8wHLR^?af4߿8Huo,xueliշoX6tbϔ'eS/ai6r]n[b;rm,kּ067<4)jeИr;xE[և}=5I;}9l@G=8&̳AVe}ֺ#OEmU$ H\Zŋ'-HJӪa+EXy sdW(+x 35t؏6>-*oTt; et-kKey)%/,Sp8Frzqx˦l6U 1.\S^ʽ'@^9ѯm'W=&cV@cO=UE: LQf3֥ZJٹԶ1XN̓tՒrl9o{?VҬ;7×ߩ'%kߨ>y&/b4zIq<"|9|V\~cC +qGHJN)60LXy] uniFr&vC+T(f&89>PGZ =h H  !؝Dv͉`uUH8CrUtxYG/s u2B|nYt&)M@W"w& e abzmsF mlZsÀsTou}AjrNmw(ICW%ωb 롛p:>r8 qAfxƺ(ok359n p+ab2p)#Xr Qȃʼn3qpXVNҹ}0Ԭ7Yxb.ɕC}PK0ӨWJ08Pn\qA.@i5Oś7έ q;q]>剪(dnqΜ*Ks,.ݎZZ29qM|"~slfVB݅y%ܾ< 겶:G "i8 Ǎ ծg[m*Z ]iGO-b "Z,|iקO,ru5]~ܼ7e~9D xaHgwgMW6RJXq?0[ciҍIQU;xt-}j^,x]SYX Aurw d 0P"d&AW5SωZUƩkΚܮ8x,jg9RD; 8<-Eww9xoxqm!C)18T:-G_…+xḆzT75s[ wZT_trFD{4 B8SڨF Ab2r#pinjE>)Dh՟ WQKpS]sn9fihǡTj8 Tp0YO)DP9,+OHiq,蹣XvruoxWIOON3!)b," 8Bx?bѡ<爌h@Qb0E2~ %>y56.Q5Y;u%}*܃ƯvXY%kwoOqU<⹟`;T6h}s1 n)Ұ>ewhj(f6Ky**eB,P&* 4AKP:eY0K?-egx`djŏ`zk8=elڧWwX S\ڮ 'U[pB+T^N&)$*}4s<1EE>O/ _ЛHJ ȗZL<GH.Ğv-@kCTDb0=*t |/k/~t2)t&uIA4/<L 4}48mWVMWaլ(GBɭuF|_ 0f:dm052ش *@cD1VUQoYxu!od> Yͤ(!?ByOX6tُ:3ci=dWc\<{D?ӂ1r>%sE(ِ yPޜ7"ȔbZKgL:GhU!W@E<-Y3<[ @'č5QRRI{|rx5)nJ.0SUs9L3w*qxonSѳ>.̳ eXy*LˑUoUQp7_\GMm:vyE3ߍ*(8f9"O 9p+*i;̮ [ D/U.?K2P WQ1ce$䣼(R'اǏW47ܖ)ddVn \ZẃY{\S]Ezrvzx&^)LEáf-5QbBUkNk[*>?}uk|'+<gLϒ ħe2OQՇ=s?TY,ۄ ڽ{^vzƲ'y7E."ʀs;"UtVDVOiyDį1FZ\D88㙽QB!V{?iCMfww[3 /R%aSn|Qr)Đ>r7xH,2qN1-&C8MC!ݰZbvMV4몈T,%5v]:x7z8o w1>7Hmp%*_Yy U B vafL L<'t}7٤cY*93%?lƤ7&:Oٴyl0(g^YprI TBrIܠXvu>d8p<)flot/examples/axes-time-zones/tz/backwardUT .US.USux WoFȵJIȥ9{{!,fm}f淳3?߽\p!J [i 9%(CZ_..>.~}=oÁ2U%,Rj޵uX Ypf(*҄V,[ XaF59 a8N9%[ņ`0ӯ|-_ J(<CXAA "-0 ߝSK6THG`JᔌV=8ѐA(St卖EI:nZ1G djNVUO*9݆قWR䀴ac k*׿Hd[<}ۆNp#a:"ߵ7ҦŶKVQsLPfveERúP2HYGz ͵Km$q}WBV(-\K șs{Zax,0d2CufE42cK׬i[p1;_ĭD1ۉi *}hC}wYs j#λzҿoCCY<Ȱ0%d41| *R~c=ǘ6P2qWO9|כ(5Q#smTK8Zℴe -Fg~ x n:ڨ!ָQ$vrF37UF#C-8*[9AҀ蠸]S.u͂Nu/tq/j=u\IiOu.Q]7LT=5>e7#;oo;ZnצU.'Y"T&'ؓC,MU`l2ePN4-&֡; GED2(ң ǐe<ɳ`)eF]5߶~߳ߵ' =;>l_s{j@!\zr?^hi ,{{h e'vKIm0x@JF%Y(SWk+vE}f؇_Zč&EjAeo +_N0z(,tJ}|(xSgݽ{FW;t'<_̡_fGAA޿ԭe,*@3lDzM[;k py#^ M,9p!]ǚ8Ox!z bJ=0&~2QkVn_"DmhvbGD $vJ+lR*n51lET [c EnGPA贇7OMNVC3y~\ V>&fX4ڀeq !3 ByVICj]Ǡ;IeUrTPawЊotpNETՀ+ÔM227 Mw3\JRIWvuۣ+nX |rKqFg5KO<]'Xl[J(wrjwr75܊lnM6L :+q WSRYN bbqbPuGDisb@bZrsŴd`)0XS, `/WXqw)fsq4ɱqa?PKt=D}Uk%'flot/examples/axes-time-zones/tz/europeUT .US.USux }kwFgWg oATf2#K-DzOdKD\D3o=U/7DꪧO?VSuuZѿ~҅Vl356UYKTtCnw[PM7,NY.{I^8 #^(/KQ^6QFmvFk5i&ѹΕ)w{}G@{VQdf /ՉJ#o vߪ(V:Աjdi8Z^SuLCmR3N4'dL3_jgjEMi\3"Î4؞l^Մ:z>ʹzјqJiuBRɳ4jǃtL' ՅoSuv>QyN$ 6G{J_ ꍷVkiʫa`0/to~cURD3>K$!z\Mf =j2\@]yaF4/Ϯdryb1Lէ.=Z8kمsC 1a$nyTz{^쩳{h7Q89hz꒺OO͙ iAZG4]v:ŜII[ݞEsmv6!&}tzKWwysY$՘Lx_t} >=?B84ޟE$%UD81of5'&7;.'ׯ~l/% 4!Ay/%c~(8_t>M}Od^vdB_!",Hi!./|rK0q-g\Fy<Df~G1GHG׌ؒEsjF22[ ш>f V1u=g3G,[x1X4onBdx ҼE$8 T% ɒ!jږE)DꄬM,„Z$sR/i)L$1!3ŸHsw8 WyOdɠk/AF J#F}7L k}*xf`>hOq!AĿ/рQi KKCaWQFз\߶d=SzT]ybGڨpAYn3{>y@unIr4c]okh8:qjN>OW@ۿĐV,Q jQ\+s]Ǵ+F)ocLTIgd-Az %7R$4dIXab:M-4o|Ƈ HxF2jӱr1Y _VEVjCs?@=1@USd\t|E.z.ax q7i!hٛG\OJs "F-V:L: (,+b;I.R!H 0.A*i+6TkXTu2:}EvW-XqShNlfD^)10HEX!&ax駨L*8ELn4c2P[{׷~{lXWxZuiUxd X}IK1KGĀ#4rnQgB$aTk9!a=pT<2d3.B&5}'ꖅ Z~Mf|A0!gʻ =LFEE6"f)Y& koc 5`1,Evkut bɆ|%z%i6F1:+̀; JCk@si.$N͹^h* *BSa !rfNi;,z 8+, +u-][4ui%co %Z ?G5F P& C *:FdǸ3t- WP_~7˙*PԿdQJ8Et$y*݊UB&{f~0Ƌ4=4h(vIjaUf~(-[ԒQg`;d$[Eg=YvHYv׬=|"te1q4*\:T"; )L4)SX)>u#>O;J&2g3y\"YLrXKEE%XPay㑆1cGoĒ|j fL$Z`|4 ;(jE#AN-kB AO5@OkRwٓM H.Ź'ef!ZnYx bCT2h \H|*`鷼|"a@r>R   k,=E3ձ&5Uv~oV]JD;''6^e08ewno/+eѿM^?TeQ/X KeI"IӲ˔PRB&7,HqavU9Vd7Uk$ݼ9i)8'q]J`}csI d4+(/aYI7;E803[`S$wIB )%P# qA5S($MI:##FQ94"SXkQ=d -0At,K[2'v;SiQL3Z]r+>"24li䓎 ܝ#֒77a1(1NX0~ykwZxn2#9 $ (D`I6m'F|x&6eEc,NfڎPЗfl@u9=eQ h/dqKˤcV!vŮ>Dc,}$Y~/$@fs.4#q1d͘)U~.H^ʢL]8SH˹v6hgG@rd T/%j٩.ҘiPyNQ!=VQV hUUL@`FeӧC4UqfFqlCE3FЏ }#3"}b{F2o uytn`cB-9B7mh,ՏHB" &+;Q-%'ŋ;O_[y`4/HxYC+g j]+O?~C>kyx~%Ʀeׄ CZA$Wj4pGC%¡ތU4a_#-mp0I%œg+[Iih,*fS</Vb5UL>_? `5+^֔ĈcxFyqF1 L\Iƙ4RE8 2ƘHw魶D (l' + #HRG+9"֨wWnkNym1$N0@JU{82 iqQ,M)m_ˮv"F<ДD+K6v]\hw߿*ˡEaYβQ`FKΨ|NkI!Ye!*zc**i{JW'N.Fpn!Z.1i%fkWǃAm*L֨[>1gGF 5tqAhT;d_D\XHEHuоn߶<HbgKo  :1$j0CrP-$җGXPuQq^!%HObAƋmXi~'WɣU,A^rtGk"f%{bڤ[a{ŏ!}qY3ћ Ou?WC~d\B= P戽;-dDק_OȦMSs4PN%<±ȏ@_7޽@hr!(@zH{;Qy.ivr}Ƿ~|׭OxbD뿊H25#o更τ}hD=LYqsN>R]ٮ2 t29JraYa)T]V{({-I}y 7%\@L qyjȆc8aRy+O.DLMF9t||A IɣSru̦:FTZ%db6zPNC!39zT 0A)IY[Ag2 J elBO.)7_eWSoHCZ[I*OVg|&|"2QW~<=c_g`@KNʤ6cU|甶iUtgXH qgPi)M:P{0 .u"ZVspQl#0pt9>yjxU]ƻqz35ُxTƕiVdQ|W `4in9ʸa;5Vu792M;4F& UGҤX[c\g[%L?LCêMrYz ݶk<֤]kjzq :H'Y?Gcf^G:]idX}<ܯs `_e?F_^Ya]3h3sx3ofïkfF_0JhF{JuP_BO(a]t]4n1)I]ȁ\9=(͹j=мeér{-Gh\r%gCnҪUEl)k%l1[vw9PB3x\@gǨ;êyt95hTYns`q"eo/ʈ1xҾd>g?١ZJcX, ½uzn'F_܉nщ~ӷpVY8j,i%ӷvG{]Guc〘 JX-O*o;A ʢ+A,olP*שCPl3ⲨSu:d(:,;帻uch+œTjʁK䇻*ް[וRY]qX%=9l;yvk#|Lr:_6KRe]l?N[jBXCEeAǶ(YNvF]v!t~v(SmC<̎Ҍ=*G%7Fčqr2(thKv|e+ 'aǦyNhKB08` 9sSC6>||34^puv7>b>f8jn =S;p'F+f/ -ΨɃZg1AbaOV_ @-a\NL)CIC:>O~L`_/%+;V0D!m ,>D z߽2se2SR#8 s~3ז^&8oH;o1爂w[B\Nl斢EYN W\\1EkNQ×-)w;Mٝ]pgI:[^џ?>ڞGb7>uӷ92t9/rk [9ޱU&%YVQݮw~jQ#:sn~::onS6e+)(W<,d{J>,jB8O 3:@}9R=wp?<-V-bWW(ɡUL+ eO4 epmdy戡);V ^5 b$ګ9LԑV[l7EE%6]pQ.oTKcnڡ(d/z:!|:P>8J7+5 2uSm0IqoU)<ԟ\ ʓHء zi~yhV۬hrO0ɚ64HyW!:K&ֱTg^!USPL n7XD/hhȹwNKS7>&%{'8A wzr Ԉ w◿zy%/!Șr1+YRh=*_Qe~^}UgTK]:aY*k*kvj#y[j/06eAa!WG&Y{>jU.8Bs!?z28w30Cۡza.>{=Ǘ+pWoBѻz( ާp権ПvGLJitQ}Uޟ7y/RGG5d2Mu;:|K?}W={T9ܽ->֏u/b}fK,_bұ7ђCƏVxux=4$%ٻy:\]π1fPG9쎿ف+YkSɫg=@OV4n44y ;/_]m*_6DE3aֿ] $1kgjDxT$@.2)Ϧ^-< E\u) _Bq@O'' יN9AUSo/ɏAө|#W$ITW7+SxH| ,ki-WҚL굷o rMu]6qϲh뤸+C.aW.3{at&ֵ-B> D?Ib pcHȡL ~Cˎruvڎ02 $=ӧ/Z=kpiojA2{Tgn 1n9QsQܓ:h3XA=~;lO|Fpy9x>;B~^uIȌW=Y\˯8Y/GAkp>PqB5tL0k\4v`_vP*;|_YΫ$:trp;h=D_#j=HDk0D5D_Ӛ њ+uu53#Z;`?8|D/}ww{_8Qn-oK)O'=5WLjr o6q8ś_yw8>Y&hsCpűm}41i):ٵЖIW46O;wo<~˾[aḀ̇̄xsʵY漙4vcW<)v,>u*a|SO9.pgp-h/ *TKyHpT]{gy~JTrtٟoM0lTOM7v}9UfߵK3;d'TSìH &ni -ʻgOYVn*ruz"*]U(5WtU{8})eoI]np"'/ zb{X(=(Fi^ќ4KH?LB?Tav98Ic陹gb>tyk"o=˾Tמn:q!5#coEx:MZ+r?GVt=t>?C;c;?XhQAliʆ1yc :7s[e ~}qjW)EbG\@/G }úf5)(ee96v$krߢaB-  WO\M~b{h3PW4P޹\ "ݡj6{eRz9cQTm<a VG \+ݡbES/ľ_Nҵ/.]qnߝCif|rUrJq5UhReoVo-|Aan5Ƿ\uiu.Oqyq!k7?^^¯l 9U[Z:isS%U;nmD5:T֩]_眿%Z)5o ge+\dylx"x)KܕA@plpa3[OSBSm[%G0P"! ,#ܕ&k$4a.N fF6+|:cI-qMIS&ة|-?i3ȵ  d'cj$NuR+{MG ׶q0q#q~)ǘԺ2zt팪S'>}2)6.Hצ["7vAz]$/5MQZ8[ nZN:{&Oqx/6-3W?kʐ0V@sjE p6nםf){dhKo pZڛZ)mטzsHz}tJO_5B{t#ksi=Ɠ}eI{ort5|p]؏~,R~lRzpo޹oSj86or-0OKpu-9a}[fB(+誇yzJ(/1ţPYAH"ڈ':JTyz99 5!H$—/Ӱ$Gy4מּ,xGnl^oNe Ng8ZUoʯ|@Ϙ'7&e-u ( h 6 2競K?`] pGt+X5:Dt;/f߼' be^wpG/eʒa]"UaJ>v /Nb F 4$ Cr$$קX?\V%V.&)T`SY ]Jf6vRwB(w.4BiBQʆoôJ̩.$]]q'@]7EGҌo,Rhn ZG5C7:C쁇:W&_ vF;ʇӞ{~{zuo^)Zd\S38*g@QPbd+62aA)ԴmLx75Wz~p^fd,RGŢ)1:ˠ0Nqq\z<ԗ2*lmVC]ac%{N@Rz+~a=Hبf [E]$RWZ'_ ԕV`o{*vCj-uQqa b->[wϺj5LB?l5&i+@>gFwF.^IZǓ6Kf2tzFvD t'60.+oB>á'<(|8"LYCnr-9Q_ ^!s!N*0tWޛP:TS UU9`  vĺׇ'&NOޗ6낡lq0IG#(,9E41{mY75xjRtIa) y 9W )]p Tģ{ʗ 2:d!)Z@ yJ9lW92#G.8TQ,vD)dO*9鸢^/М!خ'/nЅqVWWˈ^8-& OK>xq*Kd[JN'*I,fAYzHgٜV'.Iaw=ɑB'kd}^<1bI  F0QU.,#f 5^HO0JÃ\98GQBbun:_/kJU |D-7|'oEACzzvBsw u%CF,RUE#{(A,hdƪb' d(䪟p^ិR"Ҵƣ,K3Ӽuݦ& ׊\wƐKFcAH6Ȼ>+j+`I^MvrF~{ʼnS)m'Ռ>ѮAQJNh;㞕'3HTTm/EEߔTtfҢ7oqNo:A4[t?e-x1tWѭ\@/^jtQgmm6oE2qվItYlu#Ɖ{'d+Ӭ@孟Cho7aAtUm2oVmwI1i:Bն|E_(ߗ H00jҀ>#كLybuL)ʌ a DVܢPIJ6  {T_: 2R->HvnY2!hhC#c\Ϡ$<4/0I}i-YS5}*-^̚iwB'! &a)&؏G,pƳ"9QL+e ͬW1`EU3bŶwy$3o ֡Ox(jOe׳۟?;9~ c~wq#^N lhX ݷDir {>[ ,V DŜF{I* FMFB^mo Śf0lAEg$pcjZ C7i\6BgV %$U$N6Z盛(xhsB->ѣB MSAJ.nsOQu5!V//Yg6W Wm.'R<̵ %h϶ڝ0raNJ ,GW}*yXa8"J}9n M ]-^[h:jC+In(Kѻ^J6yEl vۈ HbR;TwOlx{xp@=l5ai,>7O&fdp9ERBn@ˊmM-j@w־ɵ& ֽV0(Su'L)7'ޢu%azxKy[] 8c-leͬ|ͽaxCW`u[1bal]Ÿ2R!US ]qnN,ET$nQUե(mc6[ D'F+(:!ܭ*)DA]J =_Tʔ"F˜88|9?_fKc7$V:*S줾$qw /тT8Ǵ4jr:rh)4r"s$j8:Szw;OW:F"CGG'q',`a)Uz4gq?`gq oHe:4a4C6Ҽ$#8t!v>[3U}*nmn4{I Wr`}@{w}x:ZNv n䈲mi)Cf$&Ѽ<'X']9eA !Iӥei8P3^NPln8>xHZE"&$({Sc5?~urz7mjÞ3fM92xd1L~࠮(ӕUr2fq4 Ɂ\ͥpg))_$"q)UOJG] $7͐)L'gƽJ3\gЀ$tz GB=qZ9+nJ$=B Og<y- f>n%YYw7%nNB/~0 K̷,޵jӜ 1 q v 5UT Ii~wH#ʠS1XmҠ]U6R"jQ! N=҃Mdޑ\GnpMEu (]t[vC PW‑zJ/~(`9 KݺɯصQ8,-vL碴۹eR}Sp<4R{[GFoQ-\J vsG wݻK\ͽc4Aw h)/prGI}Vnq@&eNNdśw59}_X_8p:PysÊEdqPz7rDR:u8qHkhM\&N$KH6Xۘ޹nN&MA],Rސ ~7oX~pxpYtn\) F: eRW6j> {Pޠ^K*7]~!+xF"ѵ| &2]2If^a@`љVUbO2FWWV,ߛ&\Ao<}BH}P/͵j:Y|;Qt +RbUrU%Kv~;ng;y+6-}-@ 1Hx(Pa/B5'ųVM\ުzWW9umY0x$Vd;ݰVaW%-Upi<5_6Y hv=R҉]+@lE8ݸח}sp톚^7v%hǀVy\VNe4E+ ~i*MUf|Q R?Ҿ#D2B$G`*^J3 :##/%]=09q'#AA/ZP4НQP?YqUn})Zw;4fVa5EU:]a>gm[sԼGEE|ksXVOE7H6\vsnU]u\ }5x-A:[1[$kfގ$^MH#/sY^#opO=I)I]{3_,jezuwlE[=}bɔ244uKR wZ#-3~>zLňyW¬ @SDθ #6U|A˥#=R= d2 AvNh[Ms*%*jJxNĀ]ՎKj]4שx 3q{0'oYw+%yWxvEUlJ'M#y[9rV*Z9̸Z[c5NjcgxtɡݽWI[!R}6jΈbݚSP#gVPCmJkf~PQYVPhzw9%nq$(?8#AFvHTGolA.ԗ:AL Za=X~REmHд!,Yd&)T7FXCnhApP ,F:z瀀ЄP0H*]a؊ljW g-oһ/gYċ9R%s]T#0!3e9l% +*0`%Q?Y+sV^T;MA2;6K[ݾi?-zxϸ6OؽUΪ?uv8p8T1kmRMQ@WK0ϔTyGM']aNWM|ue~ mK 55$FАa׏J)ʕtl_|~A|$tII aNo %t&)m p|c`|o M9[ḬU-ZH @0f6O_hOw\)?h|SiC5lՒASBfNf}\31<"L@YxZ,Fe[YcP/YO:B_\.NUSA:*BވE aq4DO4ELXxNkx}C+W=U4ہU 1JPQnޔ-tujB `UjKawdʡ0aΠcvOKΆE?iG/cP(‰@%jLbStҖn{O i\P'#-ĵ%BG [ȡ}IyGЅ͹zH-tRĂV(XڱdV2[M ~>Gׁ#ڊnE މnxj `A;|G7 0UYl!/_qwd1aڦ076"lHAdlϬ0 *"3U$rsK*Ə'g,Fr Iǧo3%i8b*zꖱph u!^ҹ!! H5]u?pXźo/\00pOÀ.(8*`1c<.ЀMX6м1v.Lr$![47WLe(s MwTw4rDXhZB jz2Ղ)oVe ʵ  _d$lAV9R7ck8_bTtʈ~?&c Qx#YjT GEHВt(9D@4z &Hrݼ2^&!M.i˲O 9A@TC 3 ^0ƻ,ΩxkiɂO|VbdQ p _(ӭV5!bRG"!zT˰zY `/cNXH!Av3ǂH6cI<0R#t]Q|Y.#l Tʕߧ ַ7ߒtՓiXE7ַB?AGhǕgݭimB,쾽hEsq>^}L׸ҡHQpΦr>bcɀ+7zWq?i{I%R--\/Kh^LkHsIiLxDQFq6qW88r` 4fR7~w=6=(mf<}"hkKźDDx2?>D q4",,M?c`ʬ"N8۰d~qwul-1s@8t1w IIf.fTt)y+WG+i 79Ri'lui04Zbড়Ȭ}p%e1 +d89w#7ƕhVv.gA8oIlp`-N48ۂexQ]giEzHDά͵ =2$UFhw2u/N; Mk="TJ֤w_측Sd %FR ̋Zf. %MM* EA$; sABTZ =W&E%1Ei- ej?D7^90_f?0=?-g%NNɢv>_1kqnP'TDFOtl/DY! XxlR69ė. 7ώ.(\%'/bܵ`Tk/Ó ƀ6 ]R-S /߯M]Ceh%4f2L2Ei+o\`&[kZ{~>wYl۟Nڧ_Üzҗf0ڞrCc|%>sЏ7} Y^o&Q S pb{ ^A'W?rt9ɌQv ixv`{m,G rk!-\3﷧霪lw6^澫֔+ :f7P.%Tn귢^7K]dwYgTV⾃yl[׿?jĠS:T< ˶Խ@x<Ȝ"9Q:gSʤ=TAmNTt\K8[|éQݽ=TeH<6Zs>h_&>D,I&ڐNJ"/R|} eOnE:Zkd OE̺L?L<}qq?g$;I5RG/NEyy޳l35cGG*7L3nLi*7QC|Kr6DezSJP#t|n"Pm$`0M]2,jw*zTfD@(v`w2ľ+w{"K/74n#T/dЋP1r%ꘋud+P%.Dm 9ΦblZ_|: %A":W`؞o8=@)}d{~7cD(\!kR9 "a|L8_m_y]HFc=KéV O0[;6|Fd3r-& B4.]\ h 7.LE+U:7Nr|ﷻy:ZZ=~}[}RSBfkGq&M-"S,$+3gZv"3Rr>C{T!X_#S *_Xxs%47xXVw9}[1pI~CVbl REf)7vB{!/w%-S4b;z&jpás p_T <#-#dQPR=h6bʝu)߭a;[ VR;TQd 69dQm@פ^iZh97q~& ngn6叩Zc<#YK'w QD,CO>wT2J~賓O3 4f +EUT)q4n^pܳ5="HuH:ߓ1{Ul/!{#[?׍E4gji^L1r21jqJ6FqrFMBZBףJ\U4BEoߞ<1BVEdfNm#R!V%&qߴpJE; ʅj֘6b b JTE~IӾ.3AH+ .: hg,Ær1r<l%pS+ѲwSZJ]]\R ),Ź(>*SWAX W.º>⻯ºG*ǝ}V:#4a:5R^-gϺMIƋ"L:,1,7ԗ8<9f+wT"[ԨZ5?$X Xbxcz띴Y% t5@ D=t](oN.b=W!38 k2jכdTa}<@*n7n,钞*ЌT4/,@Wc;c'IvsaHpx?H$敜gȅSRױ bmMD ,y=}0b+ .nCpgSƣ篟ߞ?Uai&Uۤ9%z !ph()Od=j~.tUhQ{~dp2}rZ&~t>^ߦ\JI)" <\lUzgPt.U稙!9NOhF7Z;) #3f,JV4&ޭҫ^NlYsutrlNDCk( D`XNEi֣=8ͤ2w56n&d6,nJ;BuO9׈$z'I\DjZl@lW %&MaeMtDg2R¡ٮ ~Xiq0]φCxm2{@`!P7n4F_U4Upj95 G$`Y'7ᮢ[%E,&I飣N ](}͒!L#r$p ft>wƁjs2GW~8W7D: 0,]㥂z~V/bΞuuMY|K}wpIGU .5@fYѻ8Xy= /,j/pӑN&؎Cqxn^ {d`r\~8P : dz iiCz'1v%Yepk*{_E%PWV)lAH,rcG7û7WzeCzYD.]R/pf;'T `~Y_E"ǨЦ~8kb}sL,\x'u$_q~4uR.7uiT!%x}.K;_ӮR9I7ES3mrZe XPnыmy#zO pD0{}67a^]҅A[s۩b$PR5l̮g7ɕFJRNR8 gZĢ 350oqL.Xz4*$޸3q7wU9 kfNzy\7u,c4L|t0LPk}ÃpnAl8عD'|<#н{M1efrɻwq~ߩN5 R/Nx-)sJ|NM/(S )׳XS2jim0uU]Y꯹eX>i>ML9<)B4<Ļ61&Il0Oכ%#Uܙ^tM+:]p`c&u&YooK}p-hٖd4w$:dQ1w>,zu}gv~yQ9L/Iۓˋ;JKɮw/4XC]+{[:Sn>zleeGsT]8W||fOMsRu tj}|].]YKwOհ`TX?U㢕wMU%Sur9,k,i1~! M4x]RS U6ZGjHh7%4a)7|1N.nsT VIf  2~L.s<~=yݦ_Oo3 C-c 4xLT,5Mk#igIt//RiF׺6T%D÷4t iԇq & z ?e`E^x[ɣx/7YB6miFvk BIŹytOFey˫ -?'{`͖~͞qE_d?Z;0P_mx[nH[zY~a`z^a Kur[ۨf>.<߱Lꪬ]&_4ULs(`<\ 0N$%?2l}MtQ<;o EO~yEVe;6U!ս,bc7对.8Y,˜6㍵3gtV]oӥ+*{ڂ5UScr\WEWxdIr5R$M^;ִ]狑kT\'_S!- 1CZ=6C kσu葊{䦱9f=K\}ϓfXkWQXvhٳ``eeL4+/H!-5G @cuA1MkɰɌuZ/((mU`$;LW n/a>6a!ju $GӾG^%I0:U}t%zds+O _R, ג҃zSd SeX+a]6Yrs%k_yd0YmUVrvm 0+ץK5#vt:I=@5y[?yM1NwPDM=S1bNŔݏR 4HwM+J%#V_~l{߳Vpa}LǺ>Bϯ0ebFtP&M[ @["vT}m2D)Ӕs&UW9}{!@9p(og{ȅS-Npz)M3pD*E)2Tz#[3l$Ud}˝{r8]%Z fa]*=PI)=738[6wW⁌(=r9Y?4f@~϶v|da&y%sx/IN[3:؂p;o Jw4QNnPr$S(] **d%naL)xXVcKIهj1<ٱc^N#a(f&aWsD;$j&Gm.ס"w 9z!LW`Oʓ&)'3^_/(FFS[ L/ֽf+#?I>KwjZ[` ؙ'ʶTekYMǵs\?chV80bc|2ŸQHs8hprlȢ5/ kd09䮳qBBPbb &]/6r&n!?ng)ڄ7Ң~v7aLl! m6fAt9bEU5oYqԿ ׊M c>'P8YG~ixM>ڑ6@Uno <ధ,&]gU!Fg~\vOdvy:o^n4q*Nĺu } WÄ?d—#Fh *p&ZLz"!#XQ `V *m[St-n dhs/[ʣtAx'9o]F^75r9"W%Xb^„g@),4iZuakq5޻ YVs$z\> . ]rIX =]|-|M_F{z)U; iR U^y5pC?S" 9f/5S:U̥%)2q0fy|cg0{2fe:^|OYq,Ob65IzC#!r( 4L9AYk﫣̐hu~ %m6săr䭒fB'em"I"i (\gL޶IDWuBKyн^R- 8da>2Rb$_-:[jZi~ 5$X~pѶI4^S5 k"8<:*y BQ8I< 'Ǝ5O9\?DhهMd%"G34w =ݵ3P!2d4Bx*l3ARg ~d&c@3RޑOLl{A\BǸF!5Cm(ƏutݺFK&8\gmDWvTBMk׳woN>=gٻamt[ F\t֫Zw??*x򿂎?jh:hI-1W䣢gMEfE /(D%њ@;/Y|M ;n'| ?>W$DѲ!_8MW\ŧD.NaB-mp1 9.'mV2joy"tn۽ fA sƨ b6(Bd9֋2R}Za~C^9 yegKMq&Ȯꠐw1Ki'r;asDJ7mY~djU$8! [<5'q 2\[9/?Pp0t\0FIwOhW?`^@/_I㐊=i磺lHSe/<@Hx{}uI;lqΜKbC91؈STG xgB<]^$ ^lWя2ʾ;~=q l{?}`pr?dl 0vzvO[nҷ<0I&]@*5EUdNY0SeQUUL}U0]UN+ *Gv/h(*ƛPKP\{mn/LvUT1mxkuv߉%!bTe1Uֹrff+e8ΕۦhFET!&/٨w-RA)jO‰Rop~Ƕl;.S﮶`5,EQk߿߸b\]`aQ*nU7UC 'ľaYXݪ]SQwG=]E*˴{:ߗhTDo+7fv*nv:nhRqбsӛ|Ե7Cw_Fn5r`čp`!u)]\"3Ǵ^I/U^hsvQėJt,J?V=TO*HäB SOFX%T2Vʚ%5ơm_o4&hh,(Q{C̓ʨ궨)|iBi|?iҿH=&TUz`Ə "]IՈa'32s;{j1HUQ!_D޻p>0rPZT0;̩A!jEۼCAVT+-= Ӷ%H4cQq<,FwW nu:MakNoԢ/m^ D,M f)ޘmry+P N{0+-vŴ9J'lO2: :s1԰aT}z0X,PG㓁>8V:eA*$D!M>%1 _C\s7yœ{?hSu);<$ U&ٍ971|:C_3G\pqҴbS{;w0,$=`\q*-@I3C(:{U]\føx :sLh{N,8VM}ʕ\#( c X!,Y1j)2I8#~iɁ7.&mDtjk5ӧ?E4mon{^~=[~!dAM *6sǹqy0QfCC>œphx-.?^L؅&+/QXOA*cJԙ$Kyѯ{^"Gs 膹U0ukvE<}* P#¸/]br$4?Q$Ĭ92.fjd-hO9/L9W)E҉ݶvt^nPb>jTF+5uI`)Yr^7&kI :7x"H9vXՖCh=Ӕ[##Fi݀֞ 1npY_ybH`D37*2q"aϐ8)(X%0RO@F:MfCA&HʶtK[2W '0ph:Ezu4Wohx9ph[XM鄖; -\ϑ\i|/oOv6CG/m2vAغNVEj+j5TtckrmG'w3+BBdFdOid! ʻ= 1('Qj:KT3ici7A-yki7=m(6>,%n=і2 ٌC"M\EE+M\ʸM4.re"̧n6"JPb2Msp?\x7SGdfsMHL7—crI@LHŗbY!7cnq,K)^LMMO KxJk;$zWo[ {z_0,1Pnfn^NwA}lܣ5Yۺ湘iss8Ed(Va|M͌do+4:4Nq6i8[P-'|f~匐ݐ"Zd{rZ1x_$O؜ WRháDaX'CN(n-Zxd6>k^qaU|0KT Ԓ᪻U+Lu`(Pu 8m:/:"/r[i׆/ D׻9'۾X.ߦI ȟђXj$o Y)cu$o\iD7>D!$ilNLLo Z%$)fFr)"ٝA4,/rNII9 i7t/ZtM'b~=y8U-Ox% cw˹氜ON5IN6x Ua w#OBnز -.›\GupإhP fbuE6[B5rZ>Yx^")?1GɁA? \T8z_]mqd42,\0n[r%* .b.PKt=D0|(flot/examples/axes-time-zones/tz/factoryUT .US.USux MAK@ɯx^L BKkVoͤY솝ݖTfy{9_`?Fo,AqaJk4:?*nڪ`zCwW׏e}_>pA^tZEI9C-#ED/'rDh1QY۟ԥ@\9$ɡSnZ)^ĬT_#hOb&ا  VlVfml^gviu*}duVX{Dc∃$XLҕoKPKt=D," ,flot/examples/axes-time-zones/tz/iso3166.tabUT .US.USux mWmsF+U]M]rʥJ!`$`ͧZҰ#{Z`6\*n/|]|injl -TɵܷdrkKeemeV(gJUKw>~"7G&oWӢ-xFTtR\|mwk,gK9Sm!NF^A7_;ofj`Q-l϶(T;mYx*ońkď2kUsӣ>ԅnro6μkO7%s]4_íu;m}Skj2])k)՝ۼ)~d ]*Rt]]Ss?iV!ծ0u.+Ur\s~xgXʹU;[7mVWm-vjKAb[%VUםҳ7Lm5ρ^jkS hQvsj#pdj {B&T%/k^@F8ܵ(@+6`=S||H(QU+uu-nXHU  BU[9,^F/0Qְ{;z=b֢+\bgRk @VB|;x;ԏ荘F1% G+ty7x&=hԤ jL[Dԛ)D/aժT0=^rfzKo_usp>OʵxfG>.ao3[˫H]_qɫ.o#iHLuߙ|CJ[d0zpT7ecsb0 ?wa A#@r03%\jNʔgp0bCYNtI ,UE_eeD?J^D?-M ]IpX` k5'\AHoD01*d:GKgA* ɍ`DSun @~1b@/)ALFt͏pVqG !O^-k)cH xa˰50>pHa(4.1 '<C;+uչjv4")FaT@!\xG8k10EW; |e)u~IkE&xnejK LIk7]BaAOoiL}Jrk;-o"Ŏ+\^ө^^]nAcRjwVCJsu@bΠI#phNp:@ՍL HN9' At7H|R _VqSQukWi,f z`hKĂp8 s"y4/-\arFZzTM$9e׶HvI h,X4 '8 r/ 0[ pm/iߺO=iDTK#6yQ vIq@kE RS GѺ&+#Ga%8|z;悊gZ>)f,Ij*;plL`̽!̡WSV繃!\zӑMuM°A*5|H Xr BdLp]#kQqv\' K WψX% :&C6TBKBV߸{Uч&R)Ll=0X\T ߑo[ss.4R=ϥ|".NN{T{C;,f}gKա7z#G˦ͯ<7ꇃb4\RL=)#ҏ~A8`|kC]V(]FiL{wMl7&NS:^tJN%tqYIt)3fvuM;杶=ЁLN[;/=o!\70x *(\sPޢp¬( 8 In {2J~^Vf]CwcXo45f|F٣`1ؿL&wԁ p~A*}l<r~0Z 8ɪ\e%GrbUg(Qؔ!3ӷWu#mľ%hV+R 7nĂ6Y3vJM}ػvZDf7ťCvqEC)5lvɆLf I-Ӯ]2Za4$Li=0SOT=FAoLaf+_ B6d)裛vY"0yq߲3abMdU\pL#9#cо7'Fd_6j PmM ¿fMr|)a<ߜ{<2o]XlPY:a[0[Iĝhc||5,!›*[em2T#&4ʈ5,AWDg(ՠT\䶉Z'm,C|5k27@{E!j9毮xEf.bþG,0jifpPKt=D馺o-flot/examples/axes-time-zones/tz/northamericaUT .US.USux }iwGgWg  z=Iϧ@*L-_Z{閡\##co7ߘi t "M0q$3۝c@gA$. r",2lhχq53g~#,$H%\ϩkss0j3$݆a07BөKRY̡,w1 2 /b#g$=NtwUg~"@tK8өMB4zqguNC9N.~0nC'g8p' =59zM҆ PÊs;OC_"܌CsĔ6؎ӭ-.氽qi3K0cG"& <<Ѹ%ڴ|{dΔΜO6̅Bf4i̇<0b .%)"PY1n&`Ӕ.c2id o`xF`J?=Xa8`2 Zh5ʑMIY1]N 8kg'pS3w1bAB,K = U8|fy g  _s?FfO.m n6C<ĕ%*:O1z ,w!(N21R#e @z; _ k߼:"}8^RօK4u D?&iOvw[p>RJu0vi֚fpSdeaH8]e0O&Sf4*XlC.$ qt;k,p/R" Sm~P:k>&SqKE4ҙF9JGB9J4r4I< Hns h܀b"e!弬տ^iM%fs߬K^ ĕ_feĈS|ЋRl螓w~V\ぅH~tڋÂAEJj3w`#_[@߳s:8=v k'$5ZaH p>~Jy$QQ n7KBȓY7CnAv(G6@1*Ta'c3N̊ŅJb_]o19s ,6}6)An 3#;GjdpdW)B?IB2MwOz"p{ (;"=yf>g`NF# hIե-7HY&Q'mOY1nLpu߃ ̧ aH7 2O杹hA'D i9(n -]!9?:T183u su;g*Xb}W.r3"3*p3+Dѳй-+cJ*duiY#ƈH!AdA0;aɵpF1UPJA\~;5ByȑU"(:/c r۹ ϩԬyҒ: anޞ6L>"̆Ԭ|ߑ\<'-5(|J(=I^.Tn%` S%|X=?mQV+EyAPJnŸ-!dq,ˉTs0`%$%oE&-XHcS8dz\89􆪋鶛J (qbp.I{zQjAC Oݓ84I$iZ!=p|M;(!$6̽!pBE Ī Җ0.Kܱ*aVjbmx8, 2 >`čƻ?ݝo\ll77?H돃 x f$ Z6:lm[mA{  ߹qmOX~ia\ňun^ R44_a{mjk ۢݟmV3ٟ9o\~:Rx+'9Xʁ*IS)܌/&tYq7*P-cpIyK3= Z";s^T5h) )^@c_9܎ c # =+l?" }*BqQCWydlDxwd7W}#Ol_ZC-ct??k_NyZȇg\xy]#/Ci plw#\V{ׂ )zPܐVwVPaܱEL1PS?b-IZ-+ݟA i_곦clV&>@ijU N1]DooH[i0(}m},tPTV5P_AȦS@NcjThj.%mu) Q)Hv׬b{+X6X)Mu=)' t`o,@V3ju6Z'_nUVQdq (@[GkTA&8>+9;A>z / >/bUY},cӏ l\}j{!"/w/g7.}A% 6 bhC`?K8m }\g1Ti4z~$Kݽ m31$^68}ng%Fbp)#6->MEW rնiiS7HrV8R0^>HΡ;O.0abcPxUe?]]llݡ 6K¹_z2 W֢ێxfZlzEMbU?OpK (!Ǩ|[d+L|1,7360s!D3**z. L2 y'cGU$Dڱ011&pMtg#qm ïhc>8ZɾNhBwSfl֢>\j=(mj0"q$Ŵ2!U*F(3g;]FQ=GbpM8G5iUB{;WMW{汷oJGiF*@SLrU G#e4xpv-NCïX@;|6 aa8 ƶQ8.e5јdl׆q"Rz4eGl{wv|lGVGzkiB_ģM%*64xMB˩Nx]"flw9heg-LH]q)Óc?xq0&OVS; x>B/a3J_LEһ]tT^͔ascG_d=bğ8y8y/&$p'ws۝MeE}n_v:~wxxYw?Q>,~vF f~itUI bu+s=5wP 90:yJ\o(ș+9%ʹK? w7ӗMC?1El͇C`Bb"R!b.gm%j+1{dJȂgoO"z,oww#KUhQџ0SB7qF.(_J6~[vӥxL_vv&wIA~!hNN]ܸߐ`q9s$Q{'Go666)6>8|سκFuIFrm2E3?Qe6t}Rr<|h8sD}aw`q+ %]@yqK ed M :༲w e|g J+/?Zz}#o'4V?פ A`jU~fe2zڿg<[ezg.SR 7\a s2OpGՁB7 Җ砕Rlw[QJ!N 2|GWH$HڼJȬYhP%NARZRY s YkKJ˰AVEM܍U洛/N2[QVǃ'@K{oR[_#֝?Ģjt ZSP1PNb빹U 厕H EGEL\>]a u2p0rKȫ; Iʾ8@T=7/${{µ 5= aKEpf38w8e^T8k8 wE UZj|ɵW]%g(2J0ĒD oYBSyYko[4} ê|W19Ӗ-Kc=q>Nv}hD2H~WiI?6 oeM d%0\:T+D㆝Qstta)hGU?qb7%=½ Df" DK&S<5osܹO>a* o]il31-$PtL@}ΠW[w(QMiX^)ZFk&0 k;O5ӳ3;ow650a:N`Q^.K._@hw>CuZ@BK~ !#2U:n閾P\|=1Ba UscBRx*}=YhHMuo<ϋXm; }F7s.QZ,R};% Pi, :\|fi$nKEzJ5vYvH]PNoO_S':ʋԏt$^^\ Swο=lB6N QḼCk7oh2q- KNC0g닊H!ـv +LǍܑL BܩW<(א) U^y-aj,xRAcbC)/B9h:Ƴ~YdE"aI}yȈ/'FљϤ[;Ptq?4[ / 9&"sHفe|Bf Z_:-6`oHN74[M~Ѳ4j1EGl* /]Lp YG :%dzEqX 0EKGJ UN-H ei2ڟzc\2hj\:Dr3.PeZ>Ռ(J#R_KJsShrGċbnGq%EkT9U'C$bxXnFL-NMGy0 =% t4+!eEE{v< 2&ORy($3] ??;3ADdPO`:@:)&VVE_Jo0(nLS$ݶv {$ ò?=̾4Ui/Ԝkƙ)ɓNCf^OJyJGbi6i^b'E"XQ&Nf7?w>n4sDQF!J95jHOm*5H%K/M4®P;Gn 0T I-+MYMQU0^fᗌM"]nvtނnMj4cҼtH7T!8jHB KPa ťT4(:4E&mo1݃Vql#M\Gw NMbM>C#PR}tnoF4 ]r%>-yI &ڀ$C b[ W\0o'A:F¨#a:>M8S.ơCG3YkEzd-JNl7 Ӌ83FvnEVQYBPjͽ>E2@hmĿ0^je-TrprvKOB}4܆QlWj!e #c+#ũDZ[FQ\B0yH>MOeEMaSv]yչLR"H&~$ZgηtH3S<(krrU5bA#4/ UUG'98,P.RXSGr%nɭ"[JE(}#'R[HsG̢?!?f)jd]Jۃmd`7l+˨FQlohU pٝ_Ftr rtNzבwp9߭w+ʄ\pc槥@Rb+/$aI}OxNt~͜i^2їFBNhw ry9KT#/ (ʹ WYfëEdF\͠fɒܶAGn1bIE_}) n2'25mFyAq^VXJoFo֤eQ`l!ӝQjp_REjL~XXL/ML̠xvJgxSEgCfy Ux#PBɌ .ĭBū6 qixz) T*6W Q$O<^Jr1zt%`3kK%2LJ(5i0LSEQz\D^?i]qv,2Tݐ -y^_XNy\}bMQ׈C9ANnVPüH0P>!e J5RE  sbOUE6ACLbfT"r7؞ZPkS[YĐ#z1j]sjB>D֨{ 0$Akh&}M,7?6|᫋b4adњNej3 pzbʀMۋޖ$E ;-}%X\ëh$a_\M[l@_lk*38Y%v;now{Hg]iGǪ")4ml,I_ W/spw4XP1ٖrmΑdYYi|•dVY@mƴgέ)5PW%skS.EsY.ӦF|%̰o½V43u%KQ\FrL5|d|ZDz Qۋ@"L1Sʋ#T_`EuUq/D. W,3W((QFNXr|"f2 (R'R'ޒ;e9ثkFJ|bGT?yޛ{@V_CH#apO7Fže5]}\哲(LR5VW&W0qbxK 0ЅvwU7Aa]F! ?\Md NF"/eri>g$D=GInɵ`[-s2WOoN͵YüsqJTu`ћ5WPUY{N]Џq y$NV4xskWasfnL ū#$E]jtRir43e5V%a>-Gۮ7C ~ieg d݂RFe@z7eZH PTϵii)I)#_OJMt| ^W&ɴԻ"_R7x?#3I,P~alH1K2ՙʁs狜gEKIi"H}.xR._OB!ζ2֎wBy&iNN~~QľܗUR o^lCuu\;%@>l+?H%,M,к~[sjg>H~/Y Sɘ=F"rZ⽛QjM4?d!Wn6e+xjFf1u㘑'c͍2b.4 .~ְ{'9*;P)G~cX1\[K= 1}9jkN]^,YoiLv>W91^^w>>.κЮ m K{?$=+ވ%'Z{W6 ; ꋭz]@Oν3ґ؃_9-ʏ,?_(fzXsJIi.e:/ DU+ƨ^éFѣ/$r>ez(j#(` #\JZh+CP9ϐ1~ s%(,o2ҙ;f]@04,/i$ g󻓯(Lw"Kؚ O|IP||l/RlTbĠ\N3 ' _=]Ys;Wv"p[R0D`8Na,XarZD%?1hKٍ g1._! iSoWYBK! zKK ,- vk3l~Hbf0 RπyGį SC]d8#zRhKȋNfY̚eʊJ/H_@JxOB UBz!Cu,U~$t>ھ\^{m3?ۿ.> `WY/d~5wpwQ:mj޻6m,[_b$r_wGAz%oIX@E7WfVHϝ{Y(TreEI__0Ѯ0h>#y"@ĄV^0RH<1 KrW 5تMZb->xAk@k*o)bCC6(@xre&pcYreS&3}O7;2$'hM ru#ԁ2}lqMRw3bL &I]^ skؑwp8Q`Tт]zÏb}3-TZ7UbR Dž]Ć P7I1xvyrIgbJGinSo?:|Tng~`?q¡1! צ<ä:QXp/(٤yz5dACks(sW_XkAsLx4)pp1Ozb蝙{Uԧ9X7toe} ocګÎv& O=aE]KspM=[ޤN'Ço޶sG0)YAA[W'=-͕aVc?aIXCo#Bm?'ak<r=sgj.ޟ^l)/!yBd*h᎛$9u鏿[ܭQQ3M3ůl^aLbm{A-vL Ƕ;i č7zfu*o<Ȉ 6"in4ԪGWۺJcnQ 4K)4{1i73*qA6 *>X+ 5ӾQGπ- sh]2o= o8vP bz{ǢHz9r]9r#۰EJ}Ojk囄}ҌdKI2-uogG֣р"#\-i Q'X- LZN kc'dDB\xgzޙ?e_:Z._;sViaUM2ŻY %##iVmp]kU);oィ6T(>0,jD[$<ʱʪ*ܫeFoD|k(zu'2w۱ƹWQ1>)өC8qc]@ 8:tcEu'wG_Y8Rq}ӏ?8`aapo SIp7l" ipKfݨ6jdpMޝH82 _K8 ^k&+!rF& V"-I5΢VR95VZ=jcZgG(K5ƖVfV"":CT!BU2 蹰Bȝ~  lV}@‹C_F+ ŧ@g]Z,Tbe_+|]DS4/mvΞcpPw~"󁔽 2ҧAx@ 8U.c0=C︋҅^kv4FC29NY@kg_7LiE3K<Qܾ Wdڢ~?` ,Sf/.Si. ͼa'?k!9~rUV t8қ0B%} +Sī  E^H 5rvjƬH)=?zhE쩊ؘ'm?24G+xL$(%ge%L҆쥭GFBB0,6DCA 'oe6رZ]OÛ0D! m-hzN~>V^!dOM.\% Jw@cGq;aħRv*P7oQei{wG{f  $bU6?xmSsgϔB`*y_TEpK7wF9=0笐I|`1p?HVn :[.O=ԻQS xUۿ{^Hֿ`7$W/g^WrLfףA5^8WE4%"5a%lټZPv}Տ{oE_p%6uduE.uNh9&m/$ 3[ܛmO5(9t[fxhGSEŦ]a=|[Dv H6I轏+x4W"%vג/%Ggrn3$V<*ohOgk֟&O\4s%b#2kz$t'?:}dK޿uJ&3g|5a{ fyu} {IvL~_9YS)!YÏ<+wA{{_͵z߷N~sz% W|?@$?X{|qX~8~۷'['1)mpB?a{oC𓽇yZ pk zOV[[/uTS~sǭRLxۖzWk}LHd~t/EO|`?s\`kSlyirTB- DN.Beg "ͳrERIش-2 ^#/:wYK88π:&]a祘;{$eC)iR()TF^҅'ݣgG`f-RSp8CuDٟqhR; )zZkLode6r-D'l]L[I稲B-眐ILK5C>-Va'_UT✈f>L'fk(Fg#֧2uKvz ֐(z2]dsM?ʋB,nFpNzhn``: Zp`y<quV˗Mul_ I䕹 {M[s 4t)3b]ݺ< a4aWck$ExZ,‹.g2nih'^'l-v죒WO'F:dJk%/͒^ʥo;sMMbV³R" נ9X̗jvJb}CYw U2eG2caؒU~ʹo~-JmWK+O>fZ~rt/?/:ފt˪ Ж(rz⯾2~ "`)J[`mYGӰyԶ t5Uim)\:D[BEq܍g3\̙?8l~;a."JΎ_4{c9v-l0cOcRzF+&$Y'+SF;Qu)b) 4JDţǧK> <̏x(r7Ao_X(^d(86G7<?WNw.?gqK] n^֪Jf&IRN>ɼul ;qbDݍ{BtǼ4  4"8<=kX?ԠqÉC]A!A FV #Iʈfx] vd5%2h̠/#OW/? a\[O㌆ZB3SK6ccǵZq79uŕW7PzGH MDLtܒ[l@pVdFƕfi\"5YV9ȍ?!Ó(J5w\Blp-SUF- 9>Dv(,S%& h ߕkQ FsWUxCN"ۍ:T&|94 .Â]>=TL3_{g-DoдM[q}uy7"jviGW7q̓ik+GNl&uF3BjN{H; l4F/61ަ94EUk sCZ)qpLN:\V"UׇD64N.H 6zz~xf+STBpf%88MR- didIgE>*ނl_c@mtDFCiJoi{Cɗa'd3=FҾsw?k7MnIΤ 3(?X6HFBa1Ӳ6'K=h5bTc5 [[i! e<$]5*MI:F E})i<tI&i=k kGHXw8]3";}qe_SG/*qf {c?GpI:Y; ;EҎ^<4~&,{GX0ًdW4 4_6{l*\q'kON͏uRb淪C_Nz7]_Y1S+0@?oQ|6ׁAT:Cpa [enI2}fȓ|sV}'߿:MX k ;V~g*>U ?엛PiV_ڕ$s 0'71;]ͮip3J|g4gLa=f[yZ߲]&5u u p*.L[{S WajTםwZ=wv }U}N@)%/w$ݵ^@w:*|^t! tW|wvOyzfSQ\Q{݇V]Cح@@N;sDƒy{Mefm^{[Xp>ܞ]?U-ΗG¦~r^@Xv?Xm=4voxH7z09tOwO:]rʴ/e+"tdDdu=fXՃMP2"ї{=XPW&N}P%DjUOZ`(,?jPe',[5S-ΕƬ!,>"bE$jEu}s̥?6AJXOL|F`lc{.Z=Ne$8]%@҆+/8n:o<4bvٹmo;;/JѝO4X}Pszm|Vwqۚ ϸ`z{?}{yi=DyP0L(Wxe^`ECmQIݛ j=ﲵG7ҷ5 &IApMe}!݁Hk{ɀDi+L7x[@o?H/QVAvzp̻K(#; lЍʨwx:VI;@k*|օǶSa{.Y3 MZj ]'kxv\Y$p$5gd~6Ol ֩xH #SK18P,b#\JiCϮiR  KuT2mNrdO#[ \RIH$bT!VWjF8) i[ʚ$jKZ_֦t:]|'Ge@N}XR6fs*i2\ 7j 5qs̟~v̨ۛk:]"i8)%S%SX,P9:}i8M.H[ʆeZMz:2]Eխ]sEZJU~⯛өa7)U.V펚艑\HlzhfW-n=#1%/; gqÕKACj+ɐ4&Kڔ?HL/$viz #0ni+mrNJ/9eis^ܴƆlBԒhM)qJnzh#s?~{ S27[Vb/sŖgP8zUp(lZF\]ژ#4[&K]3w^̴L4OQG\UӴ0!2i3+AOAtDeއS2%5_ʟ4~;1V6oYɡQI ]"`u"QMt6[wbP}_عMOg,Ӕs 6'j:/ P9Lǂĉ}:l:噓/Om= 8*HiXiW+$3;kMLSa!st>aY KU. YU ZU76ͥ3/д|ĈVIL 6cޯEҪ3h@ZZܶp. ÏVVNc6ѕw"m)%Ra]O,R:ss9_3/Q)*I쪙Okcr!r瞸[:Z. Cw$8σjt9PdT͂h&$(g&f]O0$.X[+jJQhY u,2Fn axq+Iʞ"$g.{KC3Y(IJqٮ/[ 8)ub1񭒳M e ԂD M/ţPKb;Pu[xN$ާh>WII"?=դː(\2s(^qH[*mdF[/נrO|o neKJ 䇻۱E;`%T(mam~-O e[=tdY b(v(X2EK0E'׻bpA+ )$!Jd?@z.\5ų6Lf6fMV1KQܪ.cN]xN*Umޭn>^c:. >3i%jw+fժ I<%|ۢΫ dɘr./ƫGz0lYQQd./N9]*wr(D]Юk-QN*0yt[نLZsq*[{B2ɘe -`}V!TXwU1C`jh(cJkZP(4t!8|2ycG9; )iaɬ5嵻PxV&];Tvl1!EF|VM4ĉ:A@Qu`!,6N4Q}wc`cbof@Y4CP{@`LrE!BnP ̳tH/P[e~nofhLEǴta%;ze>J5j#fiZ䐨pm4dW]\ۧm}8Ew]aa%Ūiux?m=nw6vy"6Z6,3VWfAq] ؠBZqZLC莟ħTE籘j%id>j}fyP9m!):eQȼ+JUeWV9; .Yr`&gM2c]Ϫ/w6P hh쵆^|ӲM.ȯ2\AMLEtӒf y u\V'f&P"!^1;Lfk\,)K&d6M%>ք!Oh&EkڱҢ֏ĉc}v2i!9F˂HP hQ4*+In(aݰuNo˕5jMVu۪͓[oؔW3 y(0KVerl.b;6rQ@hoO߂vVXcX9=NȻ"WJ:KZů[ k,/iSڧ̊6IJ\ Br'` 3"y&kS댟q# Kd-v R}65| > nL.zεvTpto$_] |O +B>y%mC)6 'l;7-(/c\q^)& ^ZWM iϠ6 5oeL8`Κ~2q]wx5S%B,0<]doz8yzbIF^i{WuBx^2%S=ݝboMI>Y יA;u5LJȡ?41F.AqÒI 4hE#Fv$sW1mWw'ŋJ0ԷU >٠N5dq^W`B^D kޙfE&q$: SIdQP)7襤֊.lE+_9h݅ .WƟa'v7¯3drFv: db%L4 #.FU\$b[XT[3G=˙7ai= 㸢iyl:lߩYSmm^xm0,O>Ծ z1o\W4wf[H0ܚ~XXO92ټ޴m_b)y~>β$ yՓxFǬKCσ@%lL\ zNR?6ѫUkFM1;zHIKfNF}lۻ6*ӚU5{AN[C+-*7Han"C[>Lҕ[UEq8C? s:UJ>e 7kAL6m))0Le}LC7$/,#*}˕u4|nó햆ys g` BP qIyf:lI+!`5tS/DdSq:s EB2-,L2l9tjYx" eam_)'6^ԣARz &H:ޤ~LNq΄ Ҕ?k˗-Z'+gm +^J2̀":_[rDh]O2†֤u9oGgW[tvM?PQ4yl29x7SLu?J=jK,{m4jR(\y=gye(p }dvas!Qv‘JHS$+غDv7_knU$ .,.q yy8vU"=p9^J06إ+5S'B 2t]Z0ĔLq]7F@Пp:R5/;ul +W?_$3_S'u| f/i5gi' {fRaZCF#@PG$Wky\`x)~v4Uu-F_FO) rU5.|1;\՗Sճ1Ծxj_Lrb@N &4⭄̅}coT%Isq|᪙|]=qBk/4"ͻĭRYd '] 2jC VH6War<(|}NhNqp{"SgGΘ.VwtwV/Pǹ]'U+2߶P-Ȋ p(p Ռ陷~ rGBM+a䬱.O4 y.U2FAJ̉mr..a+1; ]x~9fJܲnvtJcRo{UX}%SIɤHo39A$lʢ#|te:o4chLolD$I CɰFo.=l M!4^0(եX^؎&Iwr5ˌ#a LPq;mکC"+4di 3ɡ),MGaZP6a2k4t|}XElH(B|PgvZ^lJ^ \,ǰ[?:WW%~6 #Youd{"0:qǕȣ93\UH[ ]!/ԅ*WN2 ?wкcc6˭36$Q ݚK3[pqa4B9\7rT[ Yrpx M^qGxrp 'w|P(mCMZ_qJSɜ|Ժ^Ixp|;$-@?qn}xeDUПyc>b:JLﴠ2}k0bh{1Iu\^39̝IoC(֦28al&؆cC$ۺl|VIq+j(lV62F puAmƼ("sfVe 4.CC_ j_r*@]^a-9'F.,!~&3.F5w_f*L /azd9eo,ks+ pqo6(+"9Ȫ./ҥC{+L3,ikD<۬.#2M,.xũo0sl$l,H4cb ^t:|?9GķrO Vv~;ӰHph&ZYnE qk|n#tVBU+)GpkKș࣫9_d"Ã#/ ; ܲ{{a=ł,=f 8NbK L\+1pwGx{XLm0p1=Z`^ր UtQQCdS[(V -7[Ũ:dz|Gl-G׮~/H!}C0va0{*cg_ʙ]A1 Q :}fv BΐAø~Д"Ŝd3do ݹS@w.ķE#PsTgeHs汈$n&eZ"Qa au2Lkq+6r WѺ\xf34̶*\~0r6SsLԘ!,E}eUx=-ۨ/f3V+SkW?vH+͜]r 9.iss?$;3Ԣ~ 1h dO @20a,3.՗G"kFah9?ZW]Q;4}U՟tO>i3i>¶`\ #$ڧ&6 %:eDqU.@lW[ u^ 'Av=$(CXb\˺~b&Ia2<|i]IT^dy%⸏$V k`2\1tIA'xHKH܆x>W=Bg:VvV iY-xG"T2phi`@R|ךV$xTvW0;dޑ1(݆XA Gf|  5_o/rpAuDIW*hŁF׍mWKˡSq6g u6M/kq8o,TJ$Yepx-weIQm+_y3$9*m|^q):RERKh#vל eb"r0,idZs*e)p9E:bW{A`eo*#e46yKQXT+g28UhΊ>R/~xyEaҺ9N2v8hv3EWqk;' ea}unh?_+PH kl̗dlD~zZh Aa4lshIӦEUB\fܲaEGIԬYk>E^ h݃ó= P,lnB.1[⓬3Iu*Sij8|p*llzJ{B@ȧꕛ(v,dR [TQJ"bcG#}7گZB\ .a}k`Jl|zujsݵÊ$%Krcz)`TK33Ye(~ .^r,2cd^f[Up>NV:;_]g^& $gODso:j!+׋*3bZ(!FL;WS-('Rpg>N N_2`9u;N"Ǎ|yZ̳j# e f'1̣=pr쉾E}ci[ J?]Us~-~%J?$s-dm*/c*KQhb8,(̉4WAc f]!&1UxYR qR>J5cRbġ>n2"DRd\y n@cFq_"g? fJmV⬨t^954{(Ҷ83xJl8تaauMqA`M]bۑi[b+f2>"э}pj-9)O3lJ.Բ&~RHd;0h痒]zVx%`Rߗ8\ u\Mj+X_ OOƌ:1H6w#cXv 2{!{wl2Hf}/:i{EG1&G1|ƃʿwtuU>X4X citN9WzWl$;t6yg\ ˧_w!=Azoٓ;x}$INHjN 3_K 1p/yzExHkthF:%>5ɣ PiW "RNJ,wC'mw@RXXzn]%ED퓕ގhHLm,isJ+,Oo6Pd"!k).z[^}?VwOYJ=Qj4ȸ> kZ5ꠢ ~t$JA' HnNw `EbO]"-z&5_~r6IkpgŢՖb1Cpϸ.1L?lyS6`}V%be+]qjSw3W$e|8KSKIf6f~Ef B@1(g-9}j}7ʡD:aB馌}1L'np!ug=5x| "۰u?2Ph;mL*;)urQ:}iTt>OI-{| l3mku|ȯ_UK)< Dz+㷠RblR8rUVDWjn+Ӡ2S! LUL岃OD;Ou3~ y76nڣ~oiKu{릺's] >7 XQ,ZkR0 yJq|s,Z# ݪ2/a2Hp^]YX3{33&{ -!5f!3U0ъP S9pf".eMAp%Ϲ]kێ:4`1%lH'p d]3W]4f/J̰* 쪾A_$ ʅ?jk*BMФLv"! 蕢̽M IGb-xCB2#`}b HQ#c)7*mN(l\\_+U(4u!tc=Lv+I#shK#Fs'_s`Cߐܩ:{l>v(! txq2…9 $#E$tJ&%8d-/=]:H!434l<]#=#{S::̠5"wRƖ #k E2@YUE8&m[Tq (Z) A U$ϰ.֢vƤٽǙ[2 =΁(v,H 2L-ac@Lem])C$ O<Mݟjc%sX[ d-.o^#ݔ8Q1;Mdqe5vIP 3PM|c^|!);M"@(׮F]HޑQI!)^Tn6ȪNUjQnX'm?ZiB`Rdj XN 暀%rؕ֝D%N3le?OqҢ*&߈8G m, NC@L\2R2;rlȍJ3:Z"]rufۂl,l/k{el_oU>eD˥Ц;NvX$Sαǩ,ma^wp !G#?$aQSlT>*RV/&SNlfɥY!ڴ9`~))Wɋǝ*\/:CҾK.p3nMh3^^y3C%tĉH@Iok8oUG`R2o|5u@?]?EY<.%>6ќ܏M}$޻i"?NP#$ta$lI_|`AzDwKy EACtr.h3^ L2 `4٧Go7/Qb-pgx~4U [ź-#*bEAOJg> a:7YdLoN,W1i3`-Jt#vN?k ^6{s/l? d+ʜTWr0N-sPv}[0nMcf?/V7/W;F7a= WYCe1LwV6Cwׇ iSBe0"ɮ!t|0,Gr\݀] =^ 0NBZx^0;d!v(GUuk7dѤ$ {-&̾c9oo+^iz[dxqw 4qNI?T{uroLp(vF3vNY9Cne|tc+t#79؞ d4I=YX+Pw*wdHPg՚Uͩ#WE+Fut4n3L 9Tzq@to,6nnAu_c/^qކ"ɢ<#Bu_J'rq=ٝ@ U}+3*?ї0ͮ/ƪWvzmv^r/ a&&q!d "zI1f_xjo*8?ʂpU'nx=̺^&8mQebf RR+Z9%mٯ O, qyRNUMi"x)}#͚k $g$a?`zy8LHM}8E 8Sy6g(=T9U-56/n\q0]YLI!7Ur5,;ݶ gqjEZA^;Lh&'nÕ@^#^^aK=b F\EW,e[5^JAҚAmw]8\l$~zK/ֳo|Vz_0ry o/B~ňH Yt:>!g"B``@uCb˧.QmroaT<-i+)&7$^XE4xw~Q\y{pg$u ˂5Gw|d33;EӋ@Z}ܸ l 鏱uPZ{/2'[wQ8iqmeة_ҬVWPhmҙ>oX-s[ukk~,yc6vdz>:q=K;Kyɴy[L\Η>)OJ!~vT@#xiV[8rܫ,|.'V;FK{bikFFb.p)|H.8T`c1EPj*kPH 2*S/Rn>N"i!ѳRb:nxk*,uhz wO'F eWO\W':F Iy>ר%$+ JN,Y{y1Zd)~t;էӶv`[iXa=YOjq"96XD 8/]|.n{nF%d=fُ&LRGn9ax?"E1k,h;Y둷(wq.{C'D{ȌCir;E1Ӳc&wy) CU-GžXh_ .Im 9˹xdB= C9-iYW< xW |HZ46f- HOL?`%t9pQl%X?}8aWG0/O 4%z?D Yqд;x]࠰$^A>|LP6v6 hx.|ϒu}r[Bl>Vit2C=CKNm3?,&Ab ($)`JqI}tw幂86?C .YN}){)RW %UVbj!>&r`X0,\im~u}΢Y32a/fXbA☶uD)\i^1sEQKs8ѯ aRUrgomޜ r<[ NoA-@85w2K^ Ӻ*^Sx\%}* dR싱eZ\A}3< 03DqLkn-8GFI[.ɍ\VbS_ CzqwnG#6Wx?,x'8vFcpr)RChmtjױ?l{=0/妥^@M6p)rs\f Y9lN-W Kͬl)=ȨZDg" /kmdKzRCkq:ÕG{M Ds*"t{@|pӜBSՍTEgRLZRU"u;VWI_pug(?t$F26,J|\lJWPcFN+ !dy$e3W1~=zH"c迏^zeszw_lia}0_SW*|4M0ƃLY E ؗ~Sa_dƜspX* Χ"Jǜcz%LoBCoxC{*J_zrt$#~ E_ _`xdPUg#+ cƋg o-j9t/nzp3\{ eO u q?7FY'n; j1{>t׍,,0HV=jƸVCt(%M`Gު9lrc>+Oix<̳E{AwEQR䮛b2k"y6߄_ĕyar=u]OܧB٭v)c^[Aѳyx#)F^zEo@+U.HNyYn~tّjWuRDa$l6˶I##6U-/j LQj:S^bt@ %{m!t=sCuPAN5˯yc}vgʷymWRN2ڐkj٪y{B4x4yMD,\Ī:rBт²D-)'{ֽ-Z޵^bA T')͢oE;f1#ȴbTm+؆+N}:@Gm7ƩС$9URTlUَϙo*8`zCg\dsʻѥv<#45JA߇$aXM^oyp%'.dt'ۅ;;9Y|=ڴ$myoMOy]*6Q/ ެJ*Ѧ]QZ`zVΠɋ4Ci p.PjߐUq4<MydGoNZ|:i;._fqO %Ws;_ ܽ `YjnMn\DٔqL]{4N iG7’?W>~\*w0>CKX n%R{3/7Dd-B^c%Ϧ\o? {æO¬= fʾ3$W~<5ŭ/i5xЙY2{| (G"? طN)Lp* *VMЖ1|`}5y=%{GVl4j5YP"1vg;\.ˉ`+JEֶKy5 ovƜt\_-\۬w xx?&gcb=;^;e7k6*n]3^X3'[e#Wi]3 P3WEz0jUPYjy-'ixNҁ\Wm-a))*Z Hf?Q̱Y0CFNCSLP r\}u~._먲hCIPƛE~daW,Y.X>Jҭf-=9Byl!K<!k*(5+U+/)dm%Qo咨#x,b!4BVSS9o?aYFJ+ g:^ej1&Bώ6\%!j<Ą;\Jk|;ypU]C{sF}gXDG*Ň7Գ^J,5nPHT2n7eU0 &\jYq2)H& 4wz()ki [U4\ӗZ2<ܭ)4 iŒx=qZUWs$}[\u0#~ y5غc1$,Ih(_`'QvU+`iOskfsڻz(JVp A\kCY\/MGDTʍaW}0"+њ#!0)X-Q(ytbM,%9r̈IeL7 ]1̹(\1CqS*]zCۊ+-fYh0t)SKΥj1i"|I4* SgO.LW=OP6x;\ْfwCl~LFZM ^rAE7a{Z8@µ1 4hYm]ڧH%8vm@H7Hힶ2:Ov>N3r3uau z0ֻiXKʓTq3l4\βH[M aWݤ@덪c#ٱ $|;tT1̷ :x xVށL彿 X8FcQ%vi+AՙYuԯoKikל̢?g"ѷ?)H ʘH?Q2y)P;s[Qd\ Á'RP"BN{>= lc?R܋k1=hWR |Vun8 rF,Gন-AFk_W秨$#n囙ˆ.JML(Q,~k&4)7LL =# XؼZ=/_aO\Q ~c5\dsq RƞTк(IPs]#\1s=4ȉ<6oŲ -y%rt9JA_3`٨\T~;f YKӻyrEx6#`ӯ6>>KmrE7َ0;#_ Hc_l]N5mnEdlf>4EQo: 1n:OAjAڠI<[Km~syIyoCvtC~+ek8ڦ]h3o\erǾ'g6\>"EU{d]i]nה'=UdҝH?Dh]l"0!%TA׀n*ptGc7HqE~]k׭I,{Y ?NXg'K<(;_ES.!lӿ;ZtSl^͑Q,tdK6_KW(zC F? ɂg_wqSR81M_؊zڡ& dLʼn9ukmQ' PKj٨(`uYx}|4{9'N[ nHju,Afd}1ꍇVF՛نB&(& 1W3FGu*oUڢYp=n9 */3RECW$ADC4),82FCr; N\r?8L2ܝZA3W h0Adtxo=嫷GQ"߫Get.'Kzcؐ&Qgb~ϋŬuR]r\޺j%zvSD;M3 F3BՆ*YV' ^=vzᎸ_6An%ϨE_ANpyݺ=U;H+5W+(UA|PhkY)Mq̆d҄ӘMX2aQ瘍4gy$H+!CyXE[楺g^uEiβ$sLrHnW8ѻC:^ͫ _iK]`8MC6[y>0nWxw폈C qK836}c4yN x̘OOk85PKt=D jK(flot/examples/axes-time-zones/tz/solar87UT .US.USux KoF &\b_|hX,̌n-c!2(>b+b> FSwWU׫WX>mw}9s__Myܗ]w>mM9cVMx.P~}nq?\]L˗q\>ӿi؟c=Syߍvjz;éiۗ~RN?o۞wy? 2Mԗ_];w<uzzR}دؗ<>}qI#רq8n? Hjw}MCp[<7ۏCqݷqk" sqY -{k[g奙?)1Q Q)'"LOi"0 QQ<)ML!B4Dӣ3? o@xeQ)cXCH#*lTZۨ[p zF m`oϚ_uT5#^! # H`bIAVxA9H%61GڷO ht1 (g%~R٩Bv5#^FQ0|kdb^f{xVÈD[8A\y? )cIyE3Q * dV)Gb D%2FÄ1R{+m6!J)4h|#!el|ɶf]e۽3ٛa% qnRl{'H*!DS%/z^$FT#T!#F, +⥱+ 'DJ^RfP2HTH$V^3dT؊D4GD˄Y $lA6! "a BvK3IB\VJgJQ4(HH@"A!uDҢD#šX RiBv( F슧 ]q,7TՄ<-!#VMu:,R-yvӃ^M+]A4 _ڟ0ڿ~a$ 14$hL@"H̶"IWPB N1-FФ;ۉ&] #o&2be2]Z&: 36I&$0dՀ+FJS1;"4ADʫe"jU)+&,4&bޕY@D| D m_@b€PW>뼁&MeƒЌ׭p 4YyÄ!υ`Hs03f"0+hӝ!E@x{.j!]ǜiӹh`t:s.V 8N33 Jg gr뙄&B6Qeu6dm6ssgs ѹ\[w>w;c]\wĥ/vmҗ{U(18H~ A<QHƌC!AEdx | y2ZHI9 s9T-HqeD؜̓n+,DTYMHLx!fV;C2Q BZ~%dŭEB,#%vhTbZnZ"Z4[˪dj̊f-DYVFT? 8}vlZ^@B>vo&ɼUGlr=~*%.(#6K$B֎D#w2&E@XvDDpJGXVAXAn,Bwudb=!HEl8}$F$-…Giq7楅 /\|(Z(Z}BPxɽյ(XVG`YBHC8}1BnBPA-1ˆK2K"_ "r@VBN$hU8 J6,M ͢EV@+q TV9]>ҜV+=^o&c Bլ tHDń DLhEĬY(-ܲLD6j:7ܣy舰L֪򉁃o 'J -f곪 Y5Lo1`Gbƒvj4"@"`HV 8)7E3LXIUk)Bcbv!-i"<cLXcwu[DL:f*zzDL8Q.= t7<`ڋD|v!`7H"<٥?DTLX.=H7]1Cf-Ä=WLcvYYv"p x)e#@\]t 9*ǜHq&dC0#ʈp98 "rD!x)MBn6ǥ `Ah 04aschV-~BBIMN"FDVG $VJ8ƊMX_KU@JR@^@`MEbKGΩ" EʾFe Kx5(^S&Ȇ U( MܪlJ[54A -4E1*&*4E4I(霛 :FN"psQ\C{NޢkxD[rDޢKlDUǨr:D&N*ӗinr?!$/tȅS B?No,Au'~WSM1(;ޖ/o&|?ķ(6et o/׻]ݩ/ݮ|黡%D^~Pw?'CO~x={}vɇioF"( ,fb|ֿ~zTw>nwvXPKt=Dggr |K(flot/examples/axes-time-zones/tz/solar88UT .US.USux n[OAx/|yPr d9@؋LGo~:VX`*NA=nOJwOfQvjͰVA'j]pipV^٬./]??aON<?L4;8i8'SL'ON# 8LbOǨPq_}WӤǗi'ݭ'aP߿-0aR:hx|Vxww7՛wmuT?nWՇTooo^}ov۶Rݸ=W/Xڽ6..sek^ GmOy3!3D̈́ 0FCDZ3D˄ 0F$6 amDmRp+*8FlB$gⷲ廴:qua$$DhLc%DՌHd}c`JzˈMdJ5FO i B' ̈lkF eiiQ. = U3b" #6!6*.U ˄ODN_p B"2Fg"$"X"1D "$Ba¤1rD[Lt Ҭr,Srĕ# :6u9/I{ /v"BL~޺rLj|KH Wɔ)FVD FJq)4߳Ia6Hآ e;>9#p)$0i# 3Jcc$A-Q4${o$Ѣ$w%҄t  MNE4V"{/PybMRE}%7-;Iɳ^\xqu,i%{qMJ{X?֟EKE-B:5BkȜO_ U+~>u`| t`{}$\Q) f|$浒4"Q3H4LDy]#jc5v ;B #:K/Ljt>;B<#&"A &Oݲ1&i ʅ:ڈ9:FÄL\ B<" f% D $7 $ۆ Bru1aAHi& |>W 1Թ-^C'f q+πL\!Ùy!h йJA`NTLnń+&|1hbb[])]֖&J7>R\ݥ/pD>k?trpD΂Yi 0FQQ 4!$@]DA>@< {js+x9$4.Dg]*iD pZygrn"{Bۄ(RRő=;]ZLTuSwi EY"-xΧI닛?6UV4%7Rx7E6!(]BoQч4 ǻ efN8ޥ D?ڜHXAT$ L,kbE"07;9K{khomUDtD]q'gi+»L@(߇ j~H1&WHHVabVD]Ԉ,NeS6ײv7F͈MHgYDl9t]EZ_HSHW1S`O*S*#a WY"vd$2A"f;4=̈́!͊ Vn#\>0Mb;  U+j򗶈ۊk 4vT'– BQ|`1;rdsmvu]6yl?p nOFMCG 00/t "@8$Fet ̦6yNL^I"f[NLea I٥{8 #O1;@|ND̈́!٥eDL@CDK/h6<.{l|IHel> $].{*_qА\ڲKͷm<"ZC K&}jC|xRpTn{D@(.E-D%S%"@/q:DFB!j)qD @ D XFC$ ~/"/J@_ I.\1+7D D&AH„ܧFN "U5"!/%L\uYSDUF' 0LڒZ4nd8D!ՠl璺.r",Daaаǭ:Z5[558v.jR2N$="6=[tk\7Jc'h4c1Ѝ 1p 3Bnr iq8qP]t6B94DG?NGk>ۏM8VʩÏO}FKwOZaO/]Q}^nj<_EݭzQMs"zѿw#7ooo>7{w}_o^6yܞ$}F*?47zWkz UF=a?*܏ث~onz+uv}SQMZ4?q>Ӹ]??w~nԇz}u{t8_]|SԟԥQPE ߫l' |qiƻ~yRyntv:~7,UT8|lya_(O}7a?O? i(ۆ0 [[?0K/޴MY]xu7Ԏ^Oq&(]w*pߺqg_)pT^] q{K:]ռ4p趧}zmA _ô{hxn0z o za`oq!yA_&`Їx T<@NC Lp.. ^iwʣ˕ H+pH8M2(4J&J$lIMB6D5Օ6L4Hx&|h *^ɄшAdL!؛+W !Bo7[V6\D2$;7:W A2Xg$1 7;f%\%Vf!R21 ҇XT~["bIBbc)0J -"F238F$k/La(8 I["( G$d"F6$D&"WWDM,>"CղCDeB{$j$hveEQ K݈RDͮ@ˍK:YNEwxD,KVc XUR#t+F6$CD!"5?ŻJ=ቐ  KDj7aHDB/uȼ&׮DT6H8"s"aH͕H &@IX^ʕxP ,%Ԃ; G->\P =M."`KrtÞI"SrsIlge6Qeu6d#[V窕5nm6rן^d^!LjC&}-lrmII&}l^EN nF#;qh " qg vWXϷ;1NY2YsP)pmȊ@p:'Ī@X$<qshWsdOɓtB>9*+Jli'@(3$W uˡ7 yFRڂy]p6S͈8fzNδYHUiA0~K4?r<NpHs"ᑰLȒP *$<XY[֝2 Da"5WX)yda)gYXD#IrYuU@X#SsY%wLE5b@dY*a2J%duVPrR ;Z\@|G|͞1<_ϟ|fq$\bZD HƐgk$n)2 Wb0J0GB>b'|:w|* s܀EPx@*,u/•[iq5RX.u* iqW0"(%PRc)X:+Ru -%&}IN*Ed} "V*DQMI#B4S(s*9rKs]hrJp*$tNA**aWr "*X^q@H"$W "pON5d$'@,2w&N4Ta0DzTW>SCZNa`i=d"sCjҽD${U#Hj&WnhZQmrEYh#[i){FXC@ MT@ޞ,-tJE7O@!@=H~@b K-Hi$PԲIb5%<apFjf+4#㐝K\iB! j$,G!"TI%\N`-24r9[ ቐ GDJIJ0Dj1ޓ@TD,mu 5AW\%Hc1YAQ$m7}. 8hREPU.P"Y6GAp%5!Ū@eYz@A0DHN2) #"d<)qLșYNr =̀09rxJ%"%AKSpZOV<@T9aꭊ܀X$"%|j~q&@dTCRxM0Z>%I,NS4%q"7[@@IY$jL^%Q4%y5&K5;7@ ODReTCddtSYBɰyלss~kNAWkμAUU yHI.@lX T_6)e{ O@hw|U#EIu|R/͢S鎧+z<_:?}:1/{5Tp*; jzݩm7(Tkww5]on_.|so|w\}0\͞aׯ_a .o/jj!B^Oumvay\ُͷ]o\PKt=D$o]"-flot/examples/axes-time-zones/tz/southamericaUT .US.USux }{s7*6Y!)6IIg=YY[^뱒2T!f)a=s&EN6ԽJD~7fe6GgF-qMTh:JZ*j4Lt-=vGn;W:HY#}"ly'u19 KdJ̦QIEji zw|>%^MEL3ILL^u-b32`RMf:L?gݱTTMMbRp-"5M^IjR:NMmu{Kp@˱!AH'g̣Qmb7}Mhz޶-, u`!fMG]B?eQLkO[4ʨӄ lBS1=g  \DEfj_kuɧd-a-i{7QGs^߫{:isۢqXj&&kg?\[vaP2;i: df"&9Pg:)h́>=}1f4vNG1xFǗ;>͙thY1Bi--ZQWq,ru?3QFEbsAȂyyD%0v[ uX1ùW'SA5QAaKɷ:3!t\{bLXۚOy.MPCMli\pT\/3ש -5>ؔ=oː:Ke;M@2|hSą,Mueٜ֡' ^f8$=!N,?"yBвbFk[hI/A4&IeЌu.oݒ̀k ,mHwˡ/3TvscVz~Fb7fl&8[>({$b5e ؂1-h`32z ڎAx7QpP?%)D)1x~A$6"HXW{8#KCE/'44n@xw}$@s5\Ҝ'83&:_V&Bu_9>9=?P?}V>~{z~D|sXQevKcvAȪA6$]i@X8~6ÌjNff)i\2޲q}bwNthC3`8\~u~pvuruqusu󭃛냿o?9ڹ~ƣi-'-˭֑l` cu\1[̓ G'я=u #tnX٠"~j\PKŭt;KpvP d{~aǷ4nmjN cU 6OC71?z|C c&G^ qgzv'(曯7VMjTIO"H+;F:0U8'SЙu_{ho0Tߒ6YoTSۥ _̰,rZOs#1;x2rb'95UXK.{asX^yʺe 5C[几YQa5}cMP:4jkWflrD_.P.*obKZv)ص7g4`,H/^ ."ν!c) UW[a훅N%M=R32kNkf.IFupqs췃+Ȁġd&ϋ&2M}1'Drǔ#Gy7[N3R <1M'4al Kj t$4NZ&kd5M$pd1emĦ`.qd¦׎&5 LuJ*lwHx4W.S,/wvtan! #T1ݠ3 kķo=!U`wwEJs )>l-~&{tV97Mid/*leؒN;!zmut|2%zfGfNfN/ع<:Q'͔mg0*لd/eS\)XjҎ!l! )>5:aJ&go1Xh`0Yӿ3z|&oCz;]vy514썥ɼ<@'6jln3 K^ii rpä`76,&Kﱏ5xa|~A{ǽO!s͝{dGFX [k. K5-HEPÿ7A<$SLM#࿠XNw“JKwac92'0S;i 2&$L:!2q]:tNJ[#PRS)5Y27rt$hLcYU_k(Y]\=428c =#bewB l\_ٯ/4^mHiIޱY·tj$#skQ 7'zC۶Xsn*O1: ϶oA?C;bRBT7TwXYԪ 4 ӋQs,?s'RS;`Hl9tK\%bbb3:Smh86ö{h{/k уNX!% -[QѽuM4-" vG{(9]۵U{X1ʘF#`O<9Gf[7CA:C*cF`V ?R ؑ2"D,ϓ'/0#e#L+NiTw.I}av~{!~v* xE|qj<{}NU7X?u!N$G45n:!8ݢSWH$kRzWD~{_D}{n4-Ҏ <>0->C˹L5Ly`6OONT*^ݺ@V|Swu'cn1q{ J8cs @L7hYw~mGN#Z!T 23 ?n;PPHh]d5b2idxMy \h)c,`g!ݳN;U"gwܸyCyl^k:CXK(M+) d ܾD~T D;&$;w4/G $HµHF2ش{ZQȰcV8&SN*cvt2Ȧ]u 21t^De˭BdFΘXb;2Ir&巀W͊i-6ep dRp,%xgX@XXLx%h8%@@l?[q#o0H?F+ѩM^ hzB!7qx$SKlA9I@@Fϧʋ'.v5K,eW M.8o^6JYy-A6綣[~UV‚]ڧ.@,9W57/"H*шDGy*'n=@e$EgéIi5*VvcB&AU3[8p? U0un$cf059sEži/@HDdXy@m}:0sF;G´kdpO쳓8l:7k^uGw{6HjW=3gv{d;3@a|i} Ob;!&"\᳉ԙe3vNi46=~[wo4W=-vk&pWc6/gRLzmP7iЪR7Ť+%d'+MYF7f[1@< S|l/{99D"cE:K/>@3+sI0aYahA X<g'E&NG\8U P'X"Z/!+53'@J$bsjwl~*d;:HҤ>voSV: <+)OŁ; D.HcY'^gբX:'1%3)mP˩P_ ;8&+鷉,D-b%&-IH]4ں YFҒIBƞzHKVBjBX.x #"UCo,%[JJcվsd\@3KP@ !l\A"ʅICp)rUC/*=fD Üs L3b[uN1B|xϺڽ=(#%(oZjr V'mBKx1-UrcMU\ԉ)Lr^D]&/ĩ7L^"eKtX+1kb:HPs,Bgѝzy'/ylU y ӛ^cZ" c!P$Y£YZ,&ly}ʔRd $㜘q*/:_Cjdl?ŪZxJ\mn.4ղMלOJI]\18S2;gkE#&a4e!E {~0>8ϣ07+t⺏5+t6>WA/@!Ő粰iŎsy|\[s)Ss͵0b~zA0xGr SW;nusa%it. O5qMuzzILx.`erů1za[/xsA9Y9Ҭ6­ L$% yND&lIo_Q5.sF =PV_5X0!Zqw9T6H"EyYgh"ȩNiVz~V,6[W ='{A9JYSKrRt WreXZ|.d!q/\=6d}>M8PKqkxn] 8eg<׬$0a 4RGl^ *؍ p!X5|*L]tY=^`#o5`3iN (IܡYzh)k~Z$>EAږ^G"{ $+_^ clU9p&O,ܒ$>J+Vk"A~ӃyZ 3BW?O֤F}h@8xP|4^֡mC椣,좐 &Y97в]N0/ec0jYۨաo,w׷[; "V*\iO繩}nW;qD,0oH3= _щ qt3i+aLb76r)!et*~ZpK)Zh O _A3`=X^sIcZQ?H= -ƇC5ɚ.DO1i? |#9-aFT94H!FZYQ,0ĂWoe&4Zfs1ןq Ф &ŕBZ-Epgһs &E ܜ1F.-LI\ei~j#%VdcO! 5y:'fd} U[HcMQGP3W>52Y̖~zD5GvjA,̎c'O*Z*=vED@FXL 8 J8RݸJ-l v}ZViȜ:.J**pԣF.49AͿy{ & #ڝ/]HRXzoY_j=i:E5v.re<ѩ7r  ?SM_O"ԤeA9\V&I NyX+EYaEFop{q9coZs)%` jPGsۢ 20y417@ y"gGjBմғ nKINL 5g7+S~~y' 5&CVF#Pˠ<2@䳦jiJ!E " TB5SdGmuceOZ\e3/W[*F$3^;}1GFR6H2`jRf\ZPaN{ ppumm* #("Np)vI%_$V\K KP»2Av>fͫYNE/URԑ91~ }}rmT9˽ e$Q@'q *]K2TBm!ipDbt^gՋo jH1SeS[=)r5Rk9WZfb&rE]@yE~H.\g^E=t47sT[+*G\U]z4e 8CMFܕ/uN!< BXEW]m!6ijAf,.%u'0ҋct%s.3uUߚjc tZLdL[on.NN|urquvp7bYix}lC I sn y9zvi&`~b*m}.R|D 5tTs&:0G1jW]kWKFޥkqVꮇX#pBN;Y<sH^ʕ6^_lU&+cszZ^r[DHs3_VVUg?{ivYG\km|Pn(4"߉wCED-z&nV0ɞ^Q/UqYz\_G/g%tG}*2^'nb8W{D>\?L\. K>7)ohOzMg׸7RAlrp.KMc+ɍKOyH$jxc [>>fq۳PgGJol[\ G];SMhci0䶢XO-p?R}$Qw`%%ʲL+J3Cd{c\Vۨcx%{T4vwYѾRVnVn~p­b8̝F=xO8n.8Jiu*8 _:cdϘ)+ɿp&u,Yc= :̍)(&vk=|MV^ˇMbs9fM%.Tz?NJDAKWH͙DZdzzǁ39^_Lpq7 zx6c__ L[ ;Y8!\% )MjO\%m:rI_ "k̸`d%L|x8z, zF<B@pVJuyiޥ}9 D)5qsoZz3&T h j4Y9ɷԮ(ωV.<]`~i_sJ\j}yy C*cg$Oƞ[WHH~ϊ(pHYAPǔK~k),U4@j}-=!ↄo70u 1VjTz8zm'+?p/j.'ݗ8@৤^Te .Ʃ ?4ٔD"- 'C{,rFZؤTtFU~@9;&WvT g^kS|AWgiKraX\pٜ͹E&4TS!k;T3p6yw'rQ^_ DqYmJJ'.Λz+¡ |9Q 6&=b{S7(.].˝H G3@|#q WUx+;P~&e|GVR{^DucGһ,,7'V.3Di\岐˗8''K܊-D Kh!C"Y(W%N]պ*|Gz*wmZٳYa8!YuXTeT?%'5r/eY.]_#oN(֞bM|՚?:k-e%: ܻ>>;^p܌ڭ`+>Ăk9>1&f>p !/߭" {3p;erMl02 _~}aox w{Awwwx2 |=gSUʖO%TI/q^%;3Ejvd7"YɫPKk_j҉}gW9k0$=ZY2̤_%}[l~'U+o9qiԊjYNW#^Z-;Wדi e3KTɺLˤ .b]y@Fr=kzPǖ;LRU֥+jJvk]HWY(NW i Hߵf]cs;w'r-zhV̍LʠSEqQS"yl@N&:c  F{M.H*^rztFR]BH3ܢV)h0c0dDO:+f5+;k{]c:'bg^?f>uE^mWZQgXK}Y k%g"l=*5Bwa6"Re nUJj~R4 :w}qZK^AfN]9?G\N5{әo^\,;{vwo7(2XN (jbǥ3NɮPYb˲q<V'Ve5dzXc~C$98V3/_]֯}&ĝGt7+۪v ̔Q4y}ysvC{I H'pcz6Y4A_5y >b0ι&^k뮳|gClqt^oNc.|ft?TKPJT' :Źj%:XՅs|TDMȔ(rn-4K)4^N͗qo <:>zLV@`$˃.'YdWd6ӛByriP^c)Ϯ y-REhA/Hs-nrrq~q'77n|:Q t墰E-b =_~d~췢BzT9)hRLrpGs{ӏ(4?5G rձS+"E^p~u <ޥ~9 L'bdv[N0pG8p "0.Q>[9D`jQ;hy{-t/C2`VTUƮ gtu:iv1!Z(&zwJl,9ʠ}賡=*A{29ـN/tTڜҚc7#Zc#׈N鑽 [6y)\\DbwR SA4SD4vAiO`͕<@Pي+"qX{?QYg\ nyrN U~>ڗI} e\GR 8[NDad>'ĵvwNH(DK0F?R%koҧMMyQXfr:Ž@1k&U~䥃[{?* 6oIw_p}=cB' sSfۙUha"Zޘ eWBC571jLcG ȹ,$ Bu-U;i>4^h dXi:Rrœ+ФZ:O923,|_fuxfJ<}ca?1/,Aq  \V QoI3mzWUͯ Ƙ"@f uW勿-̤hda~d?ۗ ee?s;?}O:ž|YX5m!J3 mA3Bآ2Nk8Fz2ӅtuWgNi[%mBӧrbq=[$)$ A~ j+)r{udrؘn̆ac5S"1Ln@2\n=-ֱ?Qmmq[|z|dPH®녥Pm ]Sw (F+Ó+NKg%f(n(aI6{  IFI"7m6FT~[1؃hV^nG{!{PsnԢ=ǜ +<8 飥PlK)JszƐ6Q1(JԢv(}JIJ1CBЛ?奣H.{6כsy b/x<ԼYvl(ſ}8Npdh@P[[ iPLzڡXE 2mʀk%6aǎ d6na^)e6'̖ம`&^G6p1P|r"wYAc#9sşꥺq~Gvsß:Ըgl8[\/g|2ʃHf>D"8@M)ׅ|y U ֒B\QiAbcP C@2k#[HX"uߵ`&O$RV0`3`sd}0w@wS8@ps}V$H3zM< U 0;E*y8aXAE\ pE3!{Q~ d!lU YFMisQkǚ =:!0],i:IG\Jd,RUݰ,?Oef| c pa̤xʕt,@9E]Jb􅋄ahWFOT;R#M((SɣM g7k$iAƳiM[n7pR"W5N,3TL(GeB$饥g|D6 pUJ0B ҁ굯juIW}oHNfE6,A,;%< k?ZCqLSFVp@80 .A]q eUл"VB+.Ъ}$*3U,^o**sQxs+0j|op0VQ6V\tz걒~yLn2aF׳٬LAr3Ϳ[o[pjYrBU)]ws%'pm*Ȋ߫9 rnj-_Omp'Ә˜zPOht1tAu׈2-I E̷`+xPX…maq̸qfe3K]yE!EdmF9E'sjGx`=J_7*&"+zH: 5XEǴ nRPgrdXFPO05v"c11?!1d85o+)?v~W75n:) d,AG1A2^$; I"_c[ϰ=`@“.wz z>l|B]1x q0许p?Pa'馝vHDЊm~d Yjb {I`\3ʖI'ި;F[&FԲ8Z<$ GDˎنpA\ t!~#fQ/*|,aw/w c61Ɵ(ty؞G{?'燻+8|w}7E2"<(xͫĴO^ys­L FM RMVBlˁiP.Ӭkc>,'hkr];hvuoFEcvTjZijCt< FJ,y#.c`]e7uv~]73^@Rb$tەGR1(-4Q0Hc-'K|:(K(ah]$%>fp[仭r^$ ܑYyQ~$](:& .lt ȗa_U'nqA]E.ѝZ?MukZV8L}*ԽZln:5;(S9UA~ý3JP?V5sZxxI.9u#OI,d%\pX(·%1e g\ridD*KYm8Xs%T@OJ?[j'% = ĀԐϯrQEN`Sn28LBWPˬ'_0C1AqC)e,Ѻ(ьE&k<~SJ o5XΒax̫Cظ'7%\k. 8Nb9r\|]]G.fh",7.>¦0e&Cj'\TFIǁl?)c\|JN pv)k4JjX b!t++n~.%Mrm\tԈ~ϸaO:{N<hR,K6 ܳs\)!PFjM8 &8Z#h;7Òwݟ=;~;Agc_9`|& K=2e/,~ \`)vK2]_B}),~X-eeer2caiָ5B %F^{L5xigE!S槧/pex";m0-Xu /%q+#>8ke$dc#>9̊߳?\\c!n^O{g̥ _f;vzoRbiGg/t}xy7#uJ,[8Әc˗q=01 fVbV@ڼౖOq!PlÇqgƟ2I)T%ܧ ym) =!%dvVDܸ0u2chܐJca~N%5?fi7J e~!aָ4w)I܎U2KΚ}'<"W \Qn({Zܜ },DaX[.p4m͊ c n0zH$nrHWeVrٔrbupe_t.~~ǰ".ܘS5<g)/Ahw]WHed>'q.%>sF^kFoz|Ke-QQ}lfQbټ=Q~1RZ 8u|9:.gXXpP %$Q"gR)p 3ZƊe#g[I1g[a-9 ]z4. !2T&NP! cb ~Bm w(E"MEx?^JS9=.A0p8/tYٕG@$Qۀbf3u M*9C$euPh6Z>\̕AF1|[ԫ>} jIjЩl"[&iŠ%SQ.1lFd g.T@Ʒ˫B@|V2' uޓ ҬWeKaș/$]o[*bX8eD\H:Lģ8D?e.c5hP xGXeRjqgOꎏ6nnƅ:#@'rSz_ZZgl`آ ̘SUEJW~Q!{.8pţ{tV}4J2K&3m}J &RRgk>?z>geW^(7G'ӶQ/0/Q9ἇ%ڠ|F Y~7Ww-HLԳ:hk͓q/h@S~OAcZZeO1G-60{!)&g9^7R6;5yʴ%ª!R[ ]K˕1PW0i0p,|jMRaRu(?LӨi %hNN,%(ҽ(N.ĐIV:xǨ 7SCyz\@%æ4!FPd'fo ЌS7GT?쀊M k- л+cesHe_ nIxԎ@y뷂~he{o!v 8bYs#s+ta:;VTЃyAƛ7p ׉r r4_EGE%k&6ݑ29t+n8nWQULN["ȍ75zJ*AzƳJ0h Th+7Ɇ3[vg4-(VXN6ɈM(%8ɧޫ d`欸@V}Croܲ=Q쳡S_v6!˭}:R˫,#Ztq\ Rb̵+`aݹet.EHg2,%^|)BvJ6'@5K%0NEw*~"._, FV bUY OMlϽ/NP@xXRA'!>)+OzWQ6{e G3TroxXJNya^guÁU3[nm.qwv:Fgͱޖ`[}|xh:[&Y͘$&y枉#&9q&rȦag)QW`$> -lowA䱲mM4kqA&G-F["83l(a53̀[CįUŧcQU4Bw/X:a.\`Zg^ЎsuLna2OUڲiҩXy鯈/d% d=>;h՞A~۞n=mOoDbIjGG[~ &HN*b^ -VrCZ3bd P~}٬YZ^,'^1>9@KM1^ 禮20%ֱ4C$wE%K5a?ϖO.FGզXlG4=fSBl*snvqYX O8&3ܦuTH*U:Xۿ- !T)YmXڜGjǸ-_G?W?WŔ褭CzC,<{x|^7\]^jHW0Fq+dKO6t8c9乤zҭRw6GNL6i{!Q]ev*QTwCJn*܅BK8IӰ_۲ 6q 8u6N2!RM)]ùnk4{O\6\snS? ܙ@_PKt=DVjP$M)flot/examples/axes-time-zones/tz/zone.tabUT .US.USux |ioȶgW89Sz<[ݖoI*KQʯkG99ik?z[*>Ubi=X-U*h婵E\Y"Gй=<#'{8+6efgnj:zTTO"ƈAp\FC+Wh%יN%e\bg+l2vXIlptr2'>lVj6kUVܬ^eJBҫR{n&Vケgz><,Mv2)LIr dQU{~)5ʸPO8,}+ WfLZ|UXDJ̒5B~ rê/$vEZ )'L7(6w{k'Lיxڨ%;GnЇ"Lv){J8-s}y Lj/fb~'D VIBբ?M>P=^L'xrc0fy|b|]`ێe>?Ue<>5>3`iJqR.2ό9pՓk(cDwdp2`Yu xKbp[)29-Ӣ!h>aܧT\aԟJBAzK }.택܉iT=ɳv77BGG~5tlisC?˼]Y׼XroH; A˸p0X֨>:hU󃥗;(ɧFϣo/:vsAxG~ au KM@|?8 `W ;)[}oO{ ܨSl 1*e v֨aXFR.}y#]CUxcΦX!N7xLą0ͰGO(MC8so]˽Z﮾?rYDbԟֻԦƢ;܏0oq)%f3tq!fD<ܫ0&_w=ÁL$W0aXb]t_70O[M9yPX0džE;v_%07v8_D {N; /t+Z7|ɒ`>S7rXgT6,%`[o0$Gľ>z~|hdG^g G"[U# E=i5܈0G@4py.Gg܍ #!f nKrbe>` Ԯ,}.0m4d% g0ny[+8gRݤXUQgg no:=ס} wHfrtY|jWT EN܉O SqGz5[}ߚ{n2pӞ ئFAdSi>9f/$FG1=n0=ͩ5ÁC]C}E?Ҁ 2\˴R= 94ޠ^зgs6=Rq /r Փ7-8=zaOgј1 ursaWfs?v*FX!盛N BIxwU 䀞w* 49koռ꜃ZCe,r! 0r`iH< _[Mx.%4^esZ?T Gv?~y4KUb!Y[Mxűq**_=n4t;1S5[Jfh;Z;!QOj ?e/.6zT{0to 2ӷj5uN4/x͂CL3b7wv̙H։ʊ2Y{DpQCA7i\K$pT"'1ڦ[kǹtSCT uy8Qc""٪2e.cY`Ca_4|0@ !z,=Wll^_>5'ҏ(:mBG{1)~y)3oEo[ͱslX<05k)ԆetdLbE VZ *T j϶?YuCH:vG,2ZW6\ա}J:8pV8-2)%34\ mqS|}+?du1C  g|m5ңa`aїb6±|&b)uU#M.\&iF>(:ZnZL| {.kB]iD޲aDtpB$% ľkZڈ\z'r;dj2șMFZ"4H+#&;tYx4 J:eSo$~9/ՏMZN3rCN_*g@> aSm7kU3-ϚYEZt8lBÀ51gv ψgD y4kMJ`,$®l9L(ܑX (ĿI8drn2Db;Kc+iͺv4'Ckmc0-&ctA!a rX]]-`pyr ڀ sflZLڞ3N%<[t:} GK[p{A b` Q⿨+Ot}|I8waErOƣHN'%ZHϱ-V2|BA{T<]!tYC9= 4` PTNl vЬ j(]S{?ېifL+ iI3{^V?k _|dWXrx#+F@(ek8Kj5wM0D0&ۀ)wbSܖn d{d#;a^b^N?} zGW2b3/&bȇa }IȵڃAW.N9c FuK( nqz+:H [[F8LGE蹝{~G԰5/Yvu\-*W:cEʵKyE0`& {+O su˃ "TPxÒZoڦ7{ny}ʲCo- B׺FWs.nrk^_hA@&Iwwe56b(EJ'&Z,p}Yȳ _[wT&>E+켫b RҺS!:='N3΀!U*ZyCہ f{=!<7 I0_P wp K 9e@ye׬6q!2cj>MV4ٟ8VhYﮛk|;)*HrF"]Hou ۡ3Qbdɸ*m/߳)(Y7{D/xËx8(oL UmuN<\k֓ernݧiEi=跹L)Yϗˍdv SbHHrk N {C@5TlJ+A sjM.1>#_q45`](5jLْǚ=!cz.AS@ ث80'6jSbm=>+H~Ǵk5:djA Aۧ$R=^pzsq1<+Ua,ԛ+CCnx#q{l/y%AdFZD+֣a, P͆!J13{4ְXNn7XAvuH͛cn=rhb;U,v}׽=!$w d=ܱyĴT790@?h\diR0wNLD ksz\oO a;gw݃oT=a#^+y &s֙R;.N)/mٟ.Эr[b };!MHINk9M"s,߫->n3w@yAoKa\I>z&:Z[q@:u(rkD r:g~u?Я-ڋƜ͇JO듾^Tl9cE([$xlgI(OYUdr{`yY.4sfk;gXpW{1]N0|/w&gWƇh@ M4V{^&ZC a%ПcBΚY&e~_Ftvv$5gb'r[tw9cq8BpT)G:\ ^Ӱ>j3]Ws_߯uo3~+3wBܳKn5܌ 7"RfLmv׻봜p~{ʑm|2[v`KHÔuF]LC:9.Wb7mt{m&kk1Us,l2O+R fazu c4_Mc¿qMF#e&Z5|+:`<1w\d]߄z *D UNF!)r! Ao7y(ZD.} yv`WMeeeV_'F' BK Y_$[8>a)d:}<_ըO)Bd|pu1|'DF0* 'O% S!~q~P&dYvE{xd~!zƐ( ?3g?›zwQUsUԬ 3!01|}p#G6SZݬF!X]&W)Y6gj+qLHhvy=׶\aW$0b03=Uyи^u@1@?ߥ~%~[;?|51 ^|i)nyriUb ]pv)՞!0oy4g)lYUQNkv'*k11Q#ڋ>a#4uڸxU)UʢnZqPihbuXN QNHg\?*v#"r R /ΣNO6G3lZmRpcFLBʩiۨ;[a0ްy;Z/5=+]JAYZ@rtZMAr4RwVCS;q7MTQ'n*0L*oo&AV$F2yZJfim 0ua wvBΗ6boEF'%|#9 f6M :Qպiax ^W?Kה@maGPK t=Dflot/examples/basic-usage/UT .US&Sux PKt=DVy50$flot/examples/basic-usage/index.htmlUT .US.USux T]o6}V~ W6"*ՒIiS .'RTIʎ7R۞_ss_-_?_C >y{QtA ~Y~Y<Sz)kR4fCR=;N|ggAR 7G[+)YhrryKÛC^2cK[WDă8*}GV7o=2/mDB ,z҈"%qLš:έ%`D(p@ |ydps ,M\)g['O; 9SxRHо*KWBqY3Go0S @ AŠhUV!` 1Zq[h1$0x 㦵`%C\[rz?p'w5 aa5 qz/Cx!krJʍha8vtݦF_#xNf<=ыA䧦b(uŅ!X"xqJѷXTRp;*vtЈ0nhKҵ9>\`̖s ^8ڿw~x [<%>$8 )'ɳýғëLgY.jS"O]5:ix~؂' i+% Py)`vN~ 1P4@kHgK~<J,B®+I us/ vLINEs16?Zdx:]3'=,WB7{#79.0@a x\G%gWls6X,:08|:LptJW{S&m㓒CKriDgL*!(`k={ŤM;(1iW\-s wn #0 [qLvdIA!d+ CξN:P.!W|-s` 6P$rQ&1] »G '+dhmNC F%PqxN>;]7^y}&kSLf LA߲4S+PUሙ.!Yi {\ 4damLGX!G`A-d;7frqE5(:naU'%`(2H`4[EGYJbMl%Θx5)_C'Id9y1z`VuTpl>E*@i+Hj-lUlk Y Y\u1}JZ=gBo8BO##qzQ?8zO=Gs7 #:;\ z]jB8("ss 9W><*K41#zz+CD0b}K_(zV=HaXIr0`N.>=7+ WO uQ֑?yD/?Nc8wMOͫq# zuݩ=@oB:/'{؃}Vw8=G5z*Ϣ+NT|* d5BCD@!%Fӿy)]u[?avnkʙ֑׌C6~58ЏzƑ% _ {3$A[ʠpdس oI6;A}o$/$_9˚^q2mدG(l6#a,-c p:}S T1}ݧzGpv{fuƞJj^{S`W[5/hDx.' K#xU.0@qWk`.|0.g Dp'ntotn''mwS&n`Mh*"M |&ٹ֊Ri`pj\^0`@o, "ԕo%>$s˦+V8^a&*P+Y@)ja6V BGܲY@g ! ֺIȅ N+*t3VW1nʊ[h*}`GcLvyLjP9j;ۚÂm&;}Bgc6C @T1{ dR+T2k# g2dL%#0V42YAT62j2Z'JN&%VJM+6dʀnd6Tr2T4׍UQ`u**U`΅jU`kUȰ͌'A.G@, +~9ꕕ LJ! OɀNmPЫcpTO3L-UL%WTSsDOeFF gM:)R: i"V-d5:kkQYj@gk-ULVc=k9c"6s [K栻 MdBɰbM .@#d> Q :m 4m1 JZ6k\6ԂgU3KH;Ii?i5z)G6k!=oD}t+t((Xy/ h\dcX`Xst66zƚR=d 9a[ /ZX `U\_rBkeTɵb}^1.mɷ #ʿ7BE$\vXmP3oٺo8z5@e]*dllP?fS)e2`dG+]@ 7 ՀNV6؂X-[0.l\ wX5`pGUM%[0{˹9l.$Dr@$Jp\d7Zx8IĊ4Q #DNH&ۛJ+2QF z,!z8K9K '+ \kXe pzd@{|+߿o"s@4!R!Wqn֫J1Ḧ́SViJVYB'ɩ`Ub %`ܭu`:GBGTt9d-8{b"g $NYpUq[h4ӄ` Os9G0\: %hE.g YMF,YהN@qpڸ u!NXEN̓Qhƪpઍr8K`qຍsቹuBuJ_g f !r2&08OpɀyS#r)<NIBHlvN7sUN9IpizL$+,B-t$"KnJ7OnFMO *A%n-*h 2]"jwm"UD( kO.V@Ky .$Fwy ʥz Ut 4 5jddFXtPj75Br{bjb"t UVwGVAE Rd%R!ZR&aBVqG9$`Jĩ>npT= dYʶ]a䲇٦,;7\ *>{r+7V >h-JeR2qX`[aTA>ՐOk*;b2dٷ+G{ȑ μyp~5ֿı+{aו@leoXI@h]?ۛmT-NS7U^i&#W7[TcDVFsGÛ_ae{+ޭ ;7̾-ٷr`ߦjy/T646Z=?fks[=dϛi8mf-bc["U5rYٚu$5=\=Q&|"bm-NF5iG/B6=y=R9ի*a=A98Q:)0pz2sa9s{Q0‰BECZNp/!@D700ljn($j8QH6Dy5SȜ(DM̱ʉB=4N zN )̙Bg0?9N#I5eBk˄P2 lV:w@0᭰YF3ElU-7E@U-PWEE.1?YU0m.JtVeK^(ͳU[Y8tPzix$c1 Nkkϴmj*n/ulFW eitK Vг{񃫣 jQ'&FىijzuNى%6$m˄N %!. .WOĎ@ d. 1ޭ2Eݯ~RعQٹ";7U QAŃ/t67o-|cs_㎀V{&F>.MI8tgk=`èt [ Uvnـ^عA=tz7GzllfoF3HD ЬSpLxC+Z`熹Ws.Al$V&!a㧆kӡS~Y K*= [4lmEF9 #Vy#5IDEG03oq j`זa#ki2p IGEGS@6=-0rYԭJ6gat(eTtTpz9-TzdcqW JQcEF/G'`OGK`fVGMF$apJs0 zo,,!`me&uڊmv,ΑՌp}z:[WiB@_Umuk@4ڎBd`;lfRqKN*̑Л[GGխq(̗T(vG= D pЪH'to-2 #y#'ybb%Gnءy }gՋ˫vЖrzklm_|˝'ϖ._,a0܎o~Ų{>l?}vyywsWå/w^>zr{s9K7o'/r_^h/ܽ ~tg#nzfJ>N>؟hׯvov/O6f䗷Wۛݝrjʏ\^߾ߟ|yP;~|yzï?~+\?=yqvw'K˯/.2=7fBonD/Vd6==(QOg7?_p?axy2"<{^{0OWM8%n/<+jՀWiOL쓳W_4,`yں߾MӻcOlZ뻛w͘ 1O탘w"XHڋg֕^#n.e꿗cM˛[ٴO{($1W_\o1ՁOj?iW?]ƥ|w^bJ|}w6~gtvYPK t=Dflot/examples/categories/UT .US&Sux PKt=D#flot/examples/categories/index.htmlUT .US.USux TQo0~N %K#n*P/&9N sv x侻>xr4 P˛X|Q?#VX[ 8_V0*M'>52Qf3b,m#C6*EmɺBik ;N -;#*LުXT ż4똷E.8J뚁A5d]P Z)S9e.xujdeA 7"-aMR-nH$mTLQgr> C:7 c:Oa+{ ZY=N@2Ac7)L{al}c|&-:ierчӧF#Yg0;qROֿ˞TJX*CCiO))(ѕ6hPj4佒-Џ^vP2`){;q'e.%26F{^GpN lMMwuyY n-U+]S<)O>ә`$ةn69e_mi%lN"4A\HO<"etM!pQ+(7Yۻ(aۑtjF6JgrTK !Tkǖ1njE-:y NwTVk#³~OE BR!ECWżmn??PKt=DQ:zflot/examples/examples.cssUT .US.USux Sn0=_A(+˱=(zđD$ACR'`y _R*SnYc2S\hUҖfg:e"*-ܲ1Ѐp 4nm>[B'U n x)iS *vc"3Gv&jㅈmA΂*Nz\tl6'v[TTAc 5[$;uVӼX|{c[1Xweo{nG^Aυz7T HUN!Z©QIWm&ab u11lvj%ݕǴA3ԒQA`$Br tkI'{9Ib IHd)}?)͖& X%Pͼ7S$_>>{qwH .I> {DCGTԏiXXXXr>baz\\\WZ q5#%%}99 |@߃ # /oKJ= B||%)9+RH%(Mrm"ZqPWȈiKqS?Qs<'R{Kw _  p <|@}hI`AQxOY+ |TD#1֨b2bssf7I7VHV# <"`}ƒe;mact H)W I,s>ɢPuž)4抄n)en*߰6_]2W{Zmg@ϫN^,Wƞ97y{d$)0Dȗp .zc;(N1ԅ05ۓ7a)F+lUe`"B`:4`N?7DLE݇ ~at@GC>Q-?c]igX|o/N@CxOq  Wo)^,-7.]')cLӓUp>.o{͞Nӭm8n2ňLJ$YfpxQdOq&aESfA |v)eA>#0 =1Љf\{}J8n$!- r/6[V :jSYXII0sB=~).,m3e{'x-KP<}Ni PN"i &< !#~SJ |8 S+I nDZ[%gH8~ZXEֲLoeo8"^;^?X2*Y]- ND52VGdm p@HT 2kNd-Pen7E֮/8!}l|dVyѮFRox; svv#2s( w֎0%nfOȂ﷩Y0? HySZ:cey{P')ݍ5sha#"O(n&SJ]C?SoDCDJz#4jZ21" WG!z:56Wф]c6|OIJi:I8 r%Ŕ'"pd }@*SƓmۜC ib:KO+>`܉whKʇ-KaeV)dxa4W7d1dK|p΃hU7%^ɯڽ5[AVZ%E X6-K}EL. ̕&>Kk`"!,/W|1:y=!Ea= bm r/i.6:S-'A;;J- '{ZmO[JoûNW€DPϡ'T@{C>1)"K9!v߼s++m}st,iOWr5aÝa-δdqci7"|(geP"8$~!(w2a)|]4'Ky^һhŷOMIIcXjcR+D$ͿE<|;+(@Kەzݫ!\TP<o >Uxx,y\v_p oUIئE|IuixbkK6@[tKǺ%\-Y50.Oj˜HtEm>n0| &#<ɪ 뮌~_2XdĆ[= ='0K wGZb%9+ O=pG8(6FݺrW^PÖ G#~pwF9LLb ,z%r|j2.<=zg2cCE-z{+x,.~Z-ӂVWE&#^n$1) wvAߔsBhY45{ d׶vNYd(r;EW<nJޗEQl{Wx6 p:fC!2{*q8Ιû}%>[Gn#ODŽ9I--Y=>PV$, v '_d5?# $ޔ/Ȧ0} H]a[uP.f=J}yݦ`tJOT\P4D(Oo>nH'8xDĺtnoC!7i~SR4@7RωҜ^ʽ~EpE$۟_@a7/cȎ9 Pت<c;"g@6'%%!3 /q\?TpσkAd~ ɡoS#InAK+/YU1tBYT\]y 󂦧?cP ]հijP{Xp30㮰Rqˤ>I<2GWc! go6DTK+%GEuumU:Ɣ|6?#G$}ɸ]BO+_O=i %=/&IBOC2%kMw+A}R]ONp^5O2x,N<]i^2l4WE"mYeu}.v|cVQD*}dtC#T}_V]8qeA.t]l3h\/l$a3΂/{NiWWv,IޞrCfz`ـj ָ#wJk•gB5GnVG S|0E,Sh dz NmK6cm7J L cY/P1B䫇DŽ]$۟Ѫ,=(ג_0/Ӱ5AdTsҬY"E'QZ<׀{,('"4[LF.MգFW2M{ȅxNMA 7 h!2:1]w] w̾cX$x'r.uW|*ə윃x XտMsED).=}ی+_)R@sƸعCdu&ZC';}I}t㏛hr{]]j/ 8g"FC2g*[0ǥo覜_ s::<1S p5Uecȳ1-GR#5'VzjSwRC|n @xRC[$Qط/_".g lKXlHiJ:,Y!"yIKnJ|J;C_mڕ``w.?tːƳ_F3ByrG[7ôh dJ:oЙDa+98UsÊaWrӠ/KnN|RёҴ :z$zN΋xĭj%j9+^.zKؕP1'BVͣ+N|t{= :ӽpqDF rU?#@ B{ R[3̋r]B)<#H.`aa`וe<.sy#,j=WCmY_OZ|ƐVpuS>Vq`ApZ4ӚTDm?س` K Tyʨ1S`D ggWGpeLpT,D5EK~Es|#ܦ]f6թR(X'1 9&ؗjoGȬqxGzD`-2JCYPh0uH{2;Α\/`3F8jt]qAHU~8HVK=T:n=$4㒜 oAlɌTAuz%?oKY.<1m+ꊭ s zB|_P %=2؍ϮiZ}Ƙ#]Gæ@D2:%O r lSXÓ.Ξ@xz쿁&?<⏱Ufmmg}S-teɞa}wzҕu?%M=HQ14Do Rmª3~1-w5'܊(kDlpzH-uIxєB^tFX|(*'i'11B]Q{LV'ez 9NĂU!lm}8gZ:4ȅpD ^0珥Suedv'I[,Sgix#C\u%7I/F3y$割)wo҅J-&ugJZJ5'd|7ǀlߧO9i $E-~^5x"<~a `+W3TkU&y\S,sKNAЩK؎F0wk7I ͑:+ XŖe;z*^26`! %A& up!${͸juPi3v.Bd> ̠DJ`@V# q4c j}Zd4o&PӢA;]mWADep1r0zz,v)x3CeLbpxV*wXwk k͇NvڤYNVCTv›#_b=wy v'R r |$@70I r9)x̹E0^ucD.̙z>IpZs;Kt0OfrQ Uvz5 A6Lu10'qDy ,:Q^J;I77 NT P$g#($ >Iκ<{k"&XVd=~y:܏Gu-znҭJyKc܈Xc`L)#[rIhʌ^8e1A,bD6[]' o t)nmi3d8vZpq;ӍN]L#aZχ}IRrq2k&DoNK+P 0H_Og.U t?jEӸ+HҤ98 f2ioOm].-6ͱ\|֯*Iz."'lo3}뽷kAMe, d}NN*6:W5 3wAIͫy\S.F-B"/v(S@ 7,uީ،Dk#YC_vg;gu.ٳܞa=Ɔ63K˺?6djQY)Emg8ǎ';CUwmFy٫n$Rz׾ɍp9_[9:򌲰l$Iaq06f8*J922ARb"L!PQ Fj^U>9Y1/WvZiȩ!s^-=kD7Fxr>-׵px屏@ix5ф2Z1N,QfUT ;'>#s)2r9lT*¬hyIo<=V)խ0^VǮ3 Q\|%Cr|@ @b3xB(@yt9]MSw?o :is SVLT:8^Lx_k-q{#tUIgͫ&_$lZCuK2{7sON;ȋ$;L |L7_Lۗ䀅F{HӬx/m]WE1&=%=?ukTeo&'5Ŝr§֓@6Ye:n?x@KpN50/y\%FBUEk_W[Y:Q0Q㦆7gzlyB\CEUĘГs4fNc>K̇z&jYY:HeW^Xr&vUx5[Ziǀ4 OZ?!N'h&)ـ:\ zM!Y!Ѫ8glyKPںF|yRڍk%+_^(3,`6RsҊ\-|"jҀAd9'\?}jngbL-m8,;O6ɋ[:RrA]Lmc Z`yq,Jm7TaM>vmln<_:vJ *7YG~]&A.Dp=9ex*#=Tj*\WnmEa˒Ħ(0aЫӅR? 9S[ ,\=W#3z9\:tҟ($u[6ۻȴ޲q3"]'h9\ss?LۤKxN8/MQAdkݳYkn@`cѺI 5zE3hMMSǼzg{jd-cn|U=oCܱtg~;o=0d`x=l#Q1u frL܍s/̏]/u^}[>OFrGt`$,]f+gQR0#mR\вI׾cN00XFEEsz`u2\!1Y+=M#ކmφސ^ 5MAlb<ഹ>ͫGjﱏ*UOkY:}gCa|tl{QMw(n<-X&=]u)??/@~Dvz%Ls a3U eWHn?CSL Kgk#94+.MTk8â!zB`,+qp C/YAן5۸Ǐ^VH7n, ӈiM!xynhBfGR:hţ?621h2x sIkL6 V>2p.^g|lԒl!,>NJA91Zi!L0.3&w;lJ!uq +;#XDkM `^v E:)~d\ is>+ 1/b_d~(< DO8KO;86WiEJ,()2M\Wdsm#Vחj7zIǓXkLd:]+ksSN޺L] ** L˗V:gqgAƪVr'KlB;+FFgE9k!A>lg|[깜jŇ%ջM}Z0WQ[ˢV)>6:hٱ4"f9萯sw.gKKf@ܙZy6gk+hUyPh= "ެfⳫ.U?kϝ@s&rIdf.f+{)W'c&Oc+'P6BW'g)-?$Ӻh+˦KQEPjU|K\vg|՛MP:;rఅeӉM /,omp&Bǯ9LBobܴjbhO u*,M!gYӾ{c&g~ #1:(S7;#Cbq 01΍'hcORC ytbTƙV=өr+e4Ev,6PN9m̧]&#c`פ.TѶiQ,B  ^q*ݔVxǰ`{Q٧2 v.=Ly# dm7뾲;x5Gr fHtQQƾ5!7ckܲX"" w(!6 $Co̧ۙ Ny/ⱂyp,I^]hr<Éר\Ӧ^P2/+)Zw>a TovL (ں-m "zW'ޓzƜ+t$KFQ ǧTT汅S~wu-MJζ_qrV7Saf?mD4<*[jYZr0gMo表f67IS'tB ?Mw~:?265$h hD[ԙ(hr)h˱;0J p"pȖ(/SMU 5*G$r!dz܊ʓK,xeg ]iOk4~&v<}[΃FB&[EƼ<`n%I*n8o0r{f/̖e^iUbK)A>Wf&ťF' _*+2FM1E 4a{&]c)-{[700} bWBD۟0uA+^9pTEW~ AMڦ̤lc:r[yHozLe쮝]{_!2DIj6<#5'spn^iY1 t&7+%.WJH\9=9}ajD0@|uHd2?);{"}960lgd6O[<(gaЕ,ᰕԱ,C)kڥrsYt["vrYj S ,x_V{beK):Ͳ󫈷9fG!h)m;0?zviJ5! C3B0-:ŕ%EYwGlp(?ߛZiYdxx7~ǘɯ`B>#* !شLZt 7t- Xi˓SMAU)mw(rz/}于Q_*"Y5hjmL!wcZSj bTg;"ѡJUbIBs&FYB$"=4<58|^[C/`T0kYYb{aBvsɟS=$tdv[uEe"18$k?I&^lŮHkYn$!~AmD[D$bЋkFEdv̬UPlxm^'XfR}+WHWȗRh)*_A丰۲uF& p|dI**4<Rޮ"jZF#|b-,=9n 4%&Z3J _J,& QawЎ[bIjrq@C) 283= jsrW{ɞ5nݨ͏6 ٛ(s>Jsտ-INs :Inmulc-?Y/>)6ӯXʨO8c>~(W쌗_?~ZjZxX54u7[VK]>Gʉ5Cni. 2 y-LZݱ˘]-1!6Tk=cIt2%&+ vyZ_J/ |z[Uȁ iCs"%"u-]un=_x>f']kܷP; _ߙ(~ݤ_S= ;sRwq|CqTy*-!aSV` 53I߀$~s2 D;G#ݺtrytyV+dS{Ft3Oԑ3 HZQRY3)oA ĉե5jt~I˳ DlK0'M5/rg~ B}5cNϼ_wI,`(Wg8ό\(ڛEsuLymBX~^f1qEMeW؜}dX6'g%ΪC2uJӅ I߯ U0ܵ%i@ZÌt\nی]I]ýR_EUM':lc:bW/PDħ?7GGvR5k*WgG Elw[5N˘sfb&O-Og=/`pA=Yj;=9vBB|BdᬽAyg{^=nH,0b~$ ^{WfY| qCiiXg6Rf֦B>@ V=w<{HWl".)y}NDeR̕خ1hH34K jm!=64Unl[{%?M`՘'~.kh8 As` yxvx ǩTiJ#z4"OZ|d5ievf ֛FY: ACx~x3USYc^%$ʬu:H:GWD;&z1% q/XN4qe/~d 06l+FʑpVPߠ+c=\_iS;x`ht#.4uJ/d}jl%`o[QTFޘ7;V8dXYI0jb*^L$/ty\u"KTl@ŇNmϪmQ gtgE%yŶO΀N'LQT;KzPK,=؜Bz ^jF V2\"6璘~sNfjȳ/~VE?s0lsRzX54߳QYhdwj+ϵ&BG{NA9 zfy~ "dX[ $qo7s\βoٵ H EMǕL:Stx%993[e{S=1^],в1{]<^MUFԯT1 j=٬yXAn5y奣qwܽPyb,o}Y+0L~ʥw<@i3kaޱw`/y巗j7SqYg~0)(x z⹯ 6d/L0f,`ŕ<-5M "Nj_},SY0;&bev.BIFݡű15}rf㯅wt 罗>tGg,2mY(m5Ԧ{ck62x?2Îq _`N1&?q-i2Ҳ ecTu2@ ^u1+6㧭:A"/ 9N a* J)KS/+ qehڸxtzzqupFzZGCMT7Y,곤B?ϗRjN A&_/PôE vx1.WʪءAx31f7 VVc]J͈#qtUf$Ö:t]Se_*sbSbJwDn*luęd*4wzzW. _j>3mgn`jI+Yvj)^hhxT,/d.uQ:ìjE;(m c-ڜ=~PV{mO!r`WkGܚݞ?Ng'AWW8} S`<fQg7PHvֆhKwYvp~hÁH^i<XCWΛ"GF珼_@a% ¢L|gmh{)"3wj;uV7 Mt;KFTSE"x{ e\bròr2 ꅪ:`?-<>N[װĀ9'h=~ag{> _0߾wgR7fio,B\ fUJ*0J Q(&H):m_QmuaU7Ҟne9W/] 9xu7&%s0-o6|۟2:Y.W4h-;1]E-oiez:Y~]D Hd:C>HA&[~$-\T/W ja_?E SYW.t1*un[aŏMnam]Q?{:sT-kⲶÞa/>,;n#<)%@):}r zIsX⥈Pz3— R'E|uh*+'Y䞅A$h^yWb*%>#Kkhf|Tnwo=9I|m68ep#| J~+f؃MI9^HYc9c? XdzǿZ<Ԍ3LϛPyZs4+wdd it+i,M49,=SdあJTm2MX;Gٺ{4ݴը&2t&:@DBED A]r-4=}}d4zYYe:rᦧ׋f93uxWi饥i[)d_Q7nAZRԨs0-Lm|&ugLz:$S:~ivWYU&M}ӯ޵d#5agL *Y](ma9_Eelp.džR=l X+H+ǎ3߱!aZ0Ֆ9O3w5B%kš60Z-}\m)Gtb:a[Sҟ٘۽nΐ^mt`It}oPe1b_C6P?ig'B2OlHm*  kAi0qI[YwfLChI!:_| 8LuH[MmWb վ NiLkݦ[ݬ 9NFS+uxeiN1_6_Hf/I+KছEciϖ_UM9L8ͣ4 NEdHV$ȸ"ZΛ zgvR@0Oy/ǒ\)5#)Ral=}wpذx&0<^z74;spuyXG>}LΠj`]e̱_X{Q7)+|)Uw?u6 {k$k*yi_83.PGv<3Q.31m!B/;m R:Tݼ0 ?[މl*1 gwg s%lQY::{m ;0d ؐUֶ"4Uz="!ӗ)8)r򮬩a= r  bיuNC$gU KSV@ xy߹TTi/ɄB4E~qULϜԮ CMV/6ԜSxvr7"VP}qaVq,\6{ =wG Cҧ&j8!ݴ Ù*Me% UL$ϯC۟.،ٿrx #8Xe@mS2۽hJGfbDSP5FXTdy@ޢrK-;3~=[_)nt0B.ub`i?z WeӉ#NGÞuh@znr.辬>CKA5 \* )UOMؓ 7Z#jaTdQ+)}$˜`)q-6@\]6w9g,_YCڛ-:ZH7gH.%Q{%cYΕ!ZL\A>glor#=iaI,#~0tn{Kzc^WT+J.#)Թ[fkC)rĭ~&hkh4Oȱr Z)@C>-Ֆ);;S|8.׻7YQ ٱ%]Gjjk%s=X}UI`v6ۗͫ ?/ùKi^ ~ Hn͠GٯBrP{;$_!:繕&Eܟg_ۀ"hB/7/æC*Olٯ6ўFHèL*ڳOyu! b+ӣ3U-{֎y6ؽl,(V8QȋLI6\ĝ}hRv`KaWw/5[D"ssW;UAvT3U2v!_;ʩ ~%~clȬ76-Z)/S4&躬EUޝ:Iƍ'M`S.9J BI$Ij|-\]fRZ>b~8zEkboFeG+22Ůͧ46:yĸI3Nj:\vu٩*Yfb-j+E,=yQbm͏6#.L m$8U*T\|D! tF g 4sGe)Eo? 0]qvMY:pYqN]%o?,5%EM]\4Hչ:+8 2Nt;bef /<%2O!wFLR*Z:} &ᇋ>mVz7['UͽB^|y LH] R C$ߓL=*zݐT@6ZzswxNQ"LbaQkj9ҒLg]+ߏs|(nǁxL+B0ڒiL,/:ރ̲F߸/2v` D^`X~-SVH @J|Vjt&`%>~gnq4(:˦TV(4z¾iuqc,,O~%}bXH&m?ɿJO4 4k pxu3G͟=8Ku08^FɩT ֈ?#*wXRɨ퍁dU`vf^ ]Gfrx*3(s ?7[>Xz"A*=J"5&g],TQDWj^!s߻n nvyU%6vM ^?ѵ`=mi \G{rgXCm-*>|6O[  u]x/j e |v<%+<-nhy>Z1,er|X_**8l2@*h~gTsרl`N蘔b[dg/y5 Ш}s1DѕyR ɑ;*ҋ)@IhjvC)(Bh1VRxwCS2%aEujr&K N:xiYc@kbCK[)U͋箹QA+UbX$50m<2-;2>3XTΓNU1|[j![z" ^A>s0IU6u`7ox} 2D\F1B'~m?i`RB^4%fl:@VHfXnjiyVht*5=z]8*Lzjyu6NOJj9;+NP]mYFCӪB&Y+Jé<Ϣ&fM1.^ &9\/_0>{dC3#-\U`Mbe{0<.yiQzS}sPȖ|kIzasya*D޾{[J˨*7әSWJJL>T-L3qas璵brOXSЦM궯+cÒl.c;J{2a`xzǫԵU<G?ySpKY6_-~=olvTu΃*ܱK$ kkKugLECMM3%]LyC}Nfd ȃ;?')\uvW'h]$1q5br}S&SUHnO_mH=ֿhCkܳy`[˩JV\7(-eX7!mœ\U|:na_YV/Q5ejˮDsfhuA-:V~"15+-GϦ]iC8c|tR56αo6K%q럘ځ#JޖXONp615~r,4A lڿ\ȼ &PibHD1x o$Q(Sw |W7);#24 r24Sb *o);i\~ %{MPv̸ xK.Q9r\N>@٘TE;}0$|?:&g;^n0ӘZݠ蹳9rN2F}DΒP]yv'ccjҺEYO_ f6+ː:)2po:.2b@۸3 +Ireŋu9j:mƻ{MQc{c{~kn]dm*A.%U9עׁY^ ֋{M4(v4r)u$oHdκS6Qy)T߃//$ard+RcVf@z*g5s̴1ƅ SRz$Mҕŭh3XNMwW2h_6:tZXtF iXWz̯1+S~qΥymlYzV>>w V _ :pX\e ~Y#zeĬ'Nֆe(8_|z@[z݅#5R1PI7bJ4}#.]Q1D32$ߎ C#Go9dGf4߷QK-n +&]G1b^K1XYѲRS)RK:HsUUu\z(SB(xJMfi"1v5pݶflL#(qmݍ71WR{3*DbsS\۱ݞS5~Y8yeՔA99J m8)k +[ dv fEumGS6p2!&v=Ӆ jR4E?|yB]9A?,w4_Peǝk*_ژJr_4.Ul'6Uپ9&~WVٵ9y=dZvsx,Ճ?˚ڢf][2Y.&=? #9*#N"UkE5#0JQ@{HJc'($.s=(7̌N P#[Ҕ'"oNw2ά6x"*6`R~i]vGBOO>OTN?$x3ȍŜ~Ջ}lqy &hW'*]{?fJd?:i9_n-'asrELU>r %AH+._ՅrK:m2g VXƁu!AΞ w~J|; |iAFodo})/:N! ]ݫRUFwC |Mx֠%wkTDvmmuf#rq;ܓz&{[B3Ҝ rT'49ڇ J!ɉLf]p-|+ .iwrA+dӼLһd㥗Z手mQ Ay3APYVV1yZY:^Pu-^y/D<)wܴT=> L+zϬa B頦XGPii,þ6+`k9!/,Vb$@3_ǫ~s3.ۗ0Soz18U/b2cPj/uC}<`v\dA1) 8lyQ %"WVMU CNx"|T*:`Xd#Bſ_ã7{ekoʚ^V_#dr݅(UM{z/k'Y"}.cK/\a(^e0X)/wЇCS"iժ~+rNtA-ȢTFUYır5jSڐkl\9yFZ6=i I 1ZDg H¬A6zϙ/C6@E;U7r*O5j~3ozL˲sVbAo.P7,gr{ʞPmfm\EIqapAxcl=XG6b6Kdw2 gZJ@+'qR(/t} 8=ߝ,,'$ͨyk8`~f!6lϧ>Vw;XƳtG 쿝%2lܻupxDz(r.d[pz`ei$sΧ-A!k5H4[QBJҊURhuf5x+6uTMD-Oubixr˱ݘHw}1xw%ӝL֋۲7!j-Ea`{roHpR8Sܔ9,j.dln_&e:>W2pYMsCXQ87GtW(nWynkZMDMSO*ޖO)9Хɥ;i\YNSl<'8U wq~M5Ae @svʹ%Z+f\z)$-Iԋfd!#'P,23)%e!jn¥tJ!ФFjg ~-3*W~݋>ІxB1u`y2fg: g,֣ W( }U#,!Q#~_#ͯ2fm x-ĥ+UX/h{~\Sb2MbAmvEq0>mRg'\j3SN5P3֗|ի*wvyYo1Ǜҷ[AA"Çx ċ%u!m5?lq6,HֲJ$f{nS/iпL7D(NBtg<Nt1i(̙3Gr{?OgyZcELBD ஊ "S { ?!^gg:4B'冝JNMdXگ$aZi>ȀՆRY ?x:s3>AW5abcJu;qֲGYPF)N9(N\ۇ@fJ]d27--ę#xO,-Xx3=R|%I)m djЃ53QCY>U(-gLw<yc,#zv/r,ՇqCӪrz6-)'QS=+aoN wz) `KÔA-mc-$k֑Lml%6`FFNؓ sWeBE 9/?g~?Iz@cҮ̸3 "{KuCvhꖂAumX@lDrEteI{]cgSzX9](&n~GDQ#"Pe~m$.:GP".iV\)FdvD׾U3> s]uBx^E+e?(iIH@x*+\.p?n 3jP9,k1 ^i6&ڟ "Snn-wEJK` ]~@Kk\=8H\X;p(Q׋rؗ)rWMjn5r*֏z-RiΪ_Lk3$'dx WF3ۡ[zמb  vzxg w4@%@N) @<6#$X* 6u"u ggj 6uKXJE/Es0dT.CD[4>.4~f$-Vvk߈0hB&|up@ոb Ȥ4%~CfOYMDE26>߸9E˘bv\2h0JXWL1m_\jdySwbjP ( 6Sv ,zwqЖ{uF>\NR^gK8:5.QPHs#zu[1x6R~ ,>̺{lq1R`*-*O\ n4(٥g^Z TUں(Fg^UqZ`X GO5ڗQl֮F(\&_zMbpm--9oo1P&UkͶ Ӈt3S>Na&ϗKTZ"L QdK5q߈W&龁R]y0Hb੟s$H6ۤLd* 9Nx6֗A' @ng4ض_ 8A|Od޿4dwԣu A\0V7iHX7\}ڙ*h,W].Px:ijN/;>J&"-ƯF^eqSmkSSAGPy;S+JOG'<|\7c B✖]x~S@FޭuōĦxش^2YݜefFPl m>XC`w"#;n%tujp oFIz| |֦gr TIgP_/3Mɏ:l$ 3[`.Qeؾ:#׮[WOQtA7wz8QK792 Hɯhat fO]=;%x]T^&/29~ k]0SWQx95JI[}o(eÐmdןj>dojXYoNMl?k˽?3o3p%ۖ:HvE F+n։ɴr9k?< %Z@7Z}[RsJ8X0ځP ޸7okE;zo]=Lgpa(-Ōzo\UUm,Vɟ6aʳɦR.ZdJz8GV}9F=l30Tneb5I %u(97+C nɄ RmojyS<.^ϯ$wܐE7s1s_CXv̼#;%I^ |JUն "vsԣ=-N!V)Z\{ 3VqVM'}7v^vxn%w](vlTo] [3ƛԍ?u0iL屒ϲ/`v$cHvߵv3,&nh[PBr)U\|-%om}x F/GD 'bx(e3_@Dp m?Qx]"ZP 8}ǻ!l84W=}s^;Ts h _t1(|GgG.bL-x,X #E'-߫Gz8K6^{ƞJKSI^E6ZyQr D]6 I^%9z H#Caw͆dT̀T ÄTnp9W.;CȞ궇=Fpv\BFWN"8!)ϻ2*3Iƴv"e]@x_ѽjʖe?Gu8@.tij>VD9sVEjC[Uz)2'`ɘ72glZL;-,ngH킺 BOiAᝄܻGVwD#S-AK22Iv3n_/zzvFC|;ЖH<([5 ^\yliz"qz/ی: 6C7IlUrWg=n߷_<>Fj%+5Ϣa-G[-m]5Vw"f-<}UO] ut\|x^`jt!JGopېeESjw4RmX\ YX'Ip'"ݔ/Zmm/< #Rt7o[dU p+QKpQJµo zbvGOe>Rq&`Uۤ0ul[yB7@|0*c)!b .FWO`0 < n l"am Y ^@I r<`Ch,CI]@?[ :~J k%n7vaG(}yǂVgGoa1Dhoz@]pVl/%LSx&`Wn vI]W._ */HMWہ~@mKn5T ud!w^,ҫ%>E W NE^^17E=ś]t+`{ nllKII7xH."/!} V@ aCn^ _OmG;jv%rD DUBP cပ]^,7=(@.@4$0 ` 8@Ï ]*pv `: C !Xl:bp94ŅP{%Vo[6,ӡM*}PCBY| ;ɺ0 5IP/Kwu_q2/4VZ~'f*m`iB {v[W_) _`Rv Vk`m|0vV(mX ([f |o ͡7w:  ^{+` vF&U_%/6C{X?[1I. r$Bi%ez2pAPd?mB4L2kG$+S&*Ą0$Fd#rW~vXr,~XCy ::Jt:荙d3_ԒA;a!eXٻdRbP&Vjkwy(I5`bZ`PvʐPHeUvY`NdY p@*mq¬W(E-+P""{P2* V.9Px1LEk" #T7+vw+.8 ڡQЪ ;ܱ#}ȓgG6> 75j\jU\.˱;f:+qч;e5~#^BLhPKt=D`6 flot/examples/index.htmlUT .US.USux Wr6}bf2(vlJ3Lqj7#DB"l `Pw [bu p6ct/\[x9}oDsc٬3vWFuF&4$Q<RN{ѥVN(, AEN̝;$ +ݨkD N\?O\ؘ!R=AfĨ괓Xy/nLC+R c?>>ʺфTm3lӓ3KAU戓Y8ȹ|^aؚu:{)̢!? GX}ZR%Nj:`4 ] cj NNՊ~ E'ˆByNA-QޠJ!:/_*:C.(8Si/"9:]"(!TUE08X=c 6OE%:Ksy1|>j>nwY̊>?p+xdeNI .IIy&&)ٖF ۦۚ"԰\$܉&6NT%!'d "ZpnSn.-T:q[_.쏂?yHt\|s۽bM[D _)H 7ky#A/S93/\[2y1X#|_xii|WRj fPJ `n8 {p!K4~b2y},%=p i\.h._qҷHl؝+éiSs)M"|3jL'eja6XZ5v!8@fR"(X^dr8qa3W3QvZǓfH(Ұbkcb/td.vr$^^d w:)|:#A%4SQ-hk3.͆셍5i+SY|`b^m3 /x h3Yy@+䡐 2*KP㦡=PګTs,|Pس xӓ.u0r9xh.^!%~PkfwPK t=Dflot/examples/interacting/UT .US&Sux PKt=Dނ_5 $flot/examples/interacting/index.htmlUT .US.USux Vmo6l+[2bKNb# .a+|Eb"D96ݑ͆a`ȼ<t]/OקQ~~p|Eg?3`$»ס)׈ʖ*1#{JZ<_jSv4AWSf:H2^VNk2r!76|U䲚9zOeg H`C^hs[ʃ3 EXmB 8P9++WM=pT$51wV ͥ^ f0n-X0Mh"8C#̀"w41_ܟFzmL!ruy5+[îI)L& ]V[L ͚bc8>.JL v;ds)8!8F ;ϵ;M& 7r.GGnQIpW0\E{_/JƯp E)\)C?orl8oZnf0c h=B85w;yi2!WfDZ٣'h a{q1Ԓ8ZWpd0OكUrϜhZ2FxhݹbںΦwc`a6#?N܊ &H#BU0v^(}ߗuGI4}GH^mErw GD/VH @u4+OY'S4srۜ[JXV]SSlKAxY//޹]]"xq[ #/PK t=Dflot/examples/navigate/UT .US&Sux PK t=D:%flot/examples/navigate/arrow-down.gifUT .US.USux GIF89a!  !!!"""###$$$%%%&&&'''((()))***+++,,,---...///000111222333444555666777888999:::;;;<<<===>>>???@@@AAABBBCCCDDDEEEFFFGGGHHHIIIJJJKKKLLLMMMNNNOOOPPPQQQRRRSSSTTTUUUVVVWWWXXXYYYZZZ[[[\\\]]]^^^___```aaabbbcccdddeeefffggghhhiiijjjkkklllmmmnnnooopppqqqrrrssstttuuuvvvwwwxxxyyyzzz{{{|||}}}~~~! ,q HoL',B`2xWF` eHkdu 29rTXfdL^kŲXbɏ%n_۔iAJϫ ;PK t=Dܽh{{%flot/examples/navigate/arrow-left.gifUT .US.USux GIF89ag  !!!"""###$$$%%%&&&'''((()))***+++,,,---...///000111222333444555666777888999:::;;;<<<===>>>???@@@AAABBBCCCDDDEEEFFFGGGHHHIIIJJJKKKLLLMMMNNNOOOPPPQQQRRRSSSTTTUUUVVVWWWXXXYYYZZZ[[[\\\]]]^^^___```aaabbbcccdddeeefffggghhhiiijjjkkklllmmmnnnooopppqqqrrrssstttuuuvvvwwwxxxyyyzzz{{{|||}}}~~~! ,X H*\pÁeǰQ2 S[ ! w I_#n2RyYuP̐ IDcˇ1j|Q"E/*]0 ;PK t=D1q&flot/examples/navigate/arrow-right.gifUT .US.USux GIF89aJ  !!!"""###$$$%%%&&&'''((()))***+++,,,---...///000111222333444555666777888999:::;;;<<<===>>>???@@@AAABBBCCCDDDEEEFFFGGGHHHIIIJJJKKKLLLMMMNNNOOOPPPQQQRRRSSSTTTUUUVVVWWWXXXYYYZZZ[[[\\\]]]^^^___```aaabbbcccdddeeefffggghhhiiijjjkkklllmmmnnnooopppqqqrrrssstttuuuvvvwwwxxxyyyzzz{{{|||}}}~~~! ,^ H*8oA}sHPXLգxV-p ;,IAZ+cj8PeL-'$$BALhF]RGsӧP;PK t=D} #flot/examples/navigate/arrow-up.gifUT .US.USux GIF89a  !!!"""###$$$%%%&&&'''((()))***+++,,,---...///000111222333444555666777888999:::;;;<<<===>>>???@@@AAABBBCCCDDDEEEFFFGGGHHHIIIJJJKKKLLLMMMNNNOOOPPPQQQRRRSSSTTTUUUVVVWWWXXXYYYZZZ[[[\\\]]]^^^___```aaabbbcccdddeeefffggghhhiiijjjkkklllmmmnnnooopppqqqrrrssstttuuuvvvwwwxxxyyyzzz{{{|||}}}~~~! ,q H*ju94,7eڄq`L uw d[#alz0As,g&fGIZ+%׽|x0 ˄PB} G ;PKt=DoEBk!flot/examples/navigate/index.htmlUT .US.USux WSF6FؒMI d LJ'2<ɺ 딻?wN‚84}Xڏ~*zv|~t dfÏ/~|w{`'=2cQ.`2j^~I{/FIVD4,lu7 H?Wb>daxa{gX347ʤar>yK'K6+sGŔ!(t(2ӱ!XkǞ6+$d Lo_3:˜iUl3b9L'.R/^6ΧW~j_BllFBO"zr”\!$  R%gdabC a2dņKyK0|]R?k3g KTWXX |" $ 'ZC;cH}?.޺~ˊJM4*Mk+"յڔ'.¼c& .N8j0(+W+Km=X(u(x:uPۭ=|jך%M1o,hϝQs%hȹ`T[tt&#0ޚG*Kw̃-ŃꝔX(r5;<·aXc~5v$bq9_RL,kp:N {J@*h7H|^o]UDʛ-m}5rs+Tu3kn@w]yKGYرM|FK]AEtvOr0+Xֲۅvs(?lO(DʼngKRGĹo'h} JeyʪiԐ󪡵xOe]Ks4{ 8N& nmDd tpq ,SJ.{OC!!HwVV̦_/mڧ!Hu];&~#߯/xa_m8Vֲ}"I*QpI\ WIQZ6.X%vϹv9]µ3R)qܽaT)4V*]AhzBdEk5=ܕ:Q;i%+aPs5o=uZ=%|&ex:ȵVvfLjkNT6,DfM>Ek6@lj* P;7F8VFP*i+ͭ' ~ݠuz*haR*WE)Y;:F ;#%SwYqe_bvpĭ3V& D‰#rkf =>0=unԒf,5::`/Xb_A]#Y`w0x}١M1/ ]EFPK t=Dflot/examples/percentiles/UT .US&Sux PKt=D]D 5$flot/examples/percentiles/index.htmlUT .US.USux Ymo8 V[$8[﯉ckq"ѱhJiq@93334{y߰X?w\8%,]qbRvwտ;tzUKQZ39'x^_V\Ln6ܺh1ڭ [J+ysqijI!5[|W# Z` XZW͟lŹe׫-& A u`g}Uk꼹wSqrOBW&ywU؟@Ukޔf:O=n٤.?R[.9oq/^/6M!9>a_`hwlC9by߭Sv}OẌ́]v / \#yڑڋD^'x3\rгC5 F"zRyٙHqHqbj ǩ# 3--; f1n^ʤ.5R i )@0HcW)q@*'*QHSs4h?*p' VH} Wː(E4DGJU i% ib>hObHCҌ4.cA 6PM\-@O<4 gB:H+L@]D34tP,s1*9#@Є9BБ. h}ՎFF]sfgd 7F44 &f2R#(>nj>1 }:6$wR&1HC]k4&֪$Չ!_)).r44!1bC \`4HS:]0I=RR&$4.4H3DF&ǑG#SxÌ4ӎWH}G(84 A FwnLur4tE!c\od4#(s}C^Zw۩ iD*؂b3.ptМ h8}r05IwWC]v׈vWz\ SRnN1#68#sFRg;쮮hJAiFzN^] !@7!Dthb728 uc#|Bx8d}y]ssIҘ$OK9A: twL<F) #,'Hu?y3kʑ] Ґdi~Lka2d3"gC];=Io&/9F4m 9Cy&!O5O,{.^x¾)ުT6OԲӡ_c̺jۑ/_LtξNXm2c?& 'BU 7H ?R,OO>ƼLDhU? 3$̐vd N˼la)vv%'y{§!a?0#}̌F)ς_r4N@C6h<'? 'uue:*9t30{F2 {FWnco:/KY'SLis%͑G*EÜ+᪷mʅ`oO􊣎Mװ-XW#w)붯s^D!q,Xr^oyKu BsDn-Q2{5(:V A؃iOM3fBռK9Ubvۖ;xVV[%AtΖ|XEPoq?JjnL@f zcG^-[qK@٢kWʋƎ} />ayo [;.x"vO,ןNמ,v4Ųw$fw u3' 4CyBLddXlm+\Ҟ9%БXu[5B٪򃗬t[Ȱ]aEY;n+ݎݶB+ U 6@3Oq٦M dD$Bi\[+} 6+J,ۍ`zݵ5hmNouHrn @]7A'h),OInp!5uH]]hSg ؐ)x!{k}zy3d'PK t=Dflot/examples/realtime/UT .US&Sux PKt=D4  !flot/examples/realtime/index.htmlUT .US.USux VnF}b.UKd'h Q*m 8$.TÆP$쒺S`Y9{oo 5 ~~ k< 0y큗S°렾 ߅l4FII2"tlǯ\O"7Dbk78JTf1&Yaf#VezPd}#WU: d2  fKx`ICߟdϧ, d"_VbIZ8¡Xo)"`%3]Nk0Ob_+T7%ߠ2=9<UY~&A' eM#dNB Eb$I[4+e[SU8O 4q ,T@Fwr{$ˆm!sIx9YK4Dkjv| 2̗&) ,4Lg2FصL .ʢA-/V^2cHWZu ~١9:lZ+a ~ဴ9ֳ-1;K QzΔ Vdto[?eis5i[XB $|i$ֆWm,ԢPTZz/: eK H'T*g|{44B,GȈ[B֑/41O|#Ч,4%/cs&ٺqpvRux wy{d7|*S$enx߃84ASlLYf"ƴT^frst%/M")/6̗ 5,m-1[; ΄:i%6#PUE="t vyvf bx6O2!(6 IhPjl9R3bBWoJ&~w_Bhi]RL!-q"/+&fxS-¸}~Q?(*i5pZs3pQܯ(toSlyD\L&B(~A@R"#aדƙz%*|*h'9amL:k;Q9XT$h;#@Ie\$2IEc.ȱbŪ2069n56qA ˖ NS#|#烙v=7'}%Ԍyvt WV2ˤFh (b:3-)ܾ{azC{NTHxQ# PK t=Dflot/examples/resize/UT .US&Sux PKt=DҲ: flot/examples/resize/index.htmlUT .US.USux Vmo6 [2bK~ ƲIuF-&o%Gβa}HxG*<ئ X7 gAp1O0{ σ`ۡ`9 Q`l" +($ Q+L@]T eJm].Dj¬|o Q ##l"#ODs,MuTۨ(q!WUL& b)-ԼޠR_KY캥jf~G=vjpu gihB%_=J Ply=A5 R Zv:s8݋FOPbB))wAoda( *1`ikeV2 cEߣPo&bm, &Ď*jJLɑ;ƃi\P~άQ?%~fp1Z m+Aޚép?$ Fj#)KںD1{̝Б 4ʹ6CUq Q Yk琩V}7:vU.9 yi[E-(eUYTmHE41^g]cY*7N0Bn;5/C7xaPUT5PK t=Dflot/examples/selection/UT .US&Sux PKt=D04"flot/examples/selection/index.htmlUT .US.USux XQs ~\D%K6]Ӧk5ȕ6KKj'\&ʹՋ],w76j?A&no{  ?xmʯ`/up.A +?Q8h8Kgh:VyLL9 6S|k7(Wj՟z$D wTz϶y+xS+!(0Ș 6_=+6+Z`+H7aqq!r)[##{ff%].X&,+2DZD/>,>i/PSjR#fR[jڛhxÁ?TM-5Ӕ> RBK 55Ԩԅ=|уwUY 3܄m6m$l`kh*ljwM7֠ ]b#-{ԠBj|_V%r{2Y6aF=^]bјG.桋yb'.QyV\[p9; {^lYv8uX`6XS'ȃqoy $6pc618bt1O[mYt svv@؂OY72MxAog;|ΊYrl k@?c{ރ<^CRks:a5\Uȭwbϓnx(Z|J:\8_Rn:zcC-+52nON՞OLmMkK;ԹZ,l9ӹMB$]w5)خxct+|UZ'yZmR-h^w` m[Xa *O,tvMD[C]̂;Տ$ѳ6m;4(L[+)%?k(< }Rx?JKmrs Fk3DL4Dx=ZG%8up̾Hdlj{ }eX[*Z܍iv|b7wQY-Cą43M%)!fa朐8Ųj薲*b,q3'DWTrP xXbV,e x@F(, ܏GR%ԷM!Le3G|EV-eJsahBNuÌelb)ls"*M9=Z$&aŘ8| ˚HlIc#NkkA4X^0*e)ajBs;.CGnɠ_.dfY. &cGYȴ_* Rh5R5w]7D72~qU]3K=(d+VUSXD| }ZA.0_!X`'Ԇx9z<«@G mW"d ^c"kukG|bh՚28tDWJH퇙Dͱ'DEa~Yl%o|5كK_xo޾F!*J508tFPK t=Dflot/examples/series-errorbars/UT .US&Sux PKt=D̓' )flot/examples/series-errorbars/index.htmlUT .US.USux Wmo6V6"Kl/#h `$bK*EelKס Cy_\yw sM| ~w }_p/KoںJHyYu%Ω"K#g"RESվ_gԁJ#Gѕ2.!J̩j~h')N?szE"6-!t:r<ϧ%؋I )5@ۿhps aI)$dOdA桪ed"7g E4֑cO_ *)2=]SO3HJlF/"iϨhle%YH\ Ĭ[l{34[[\,h༄pX b_e; ߚ:Qv;xw7.L :+Q "!&tau7p==F FO5UZzGN5Fe-`15^,`HSDp!<:.hPZj\$_bkw) аv\,Y$y`GwD21+&8&+lIs!%&Sr{3V)5p;Ы{%~, L vZkjno;./ grڡsGꡃuNAnj(% i:S j[F_= "-9wvXJH#O \o'@?573Ii/yz{uҹ>d*KM-RjRD8pQi1X_?mnfw^z>͗M燌&ǘNZk3Vhd"g1T -r* ě(6{Y5Mȏ6ʜ>נ=/![$Ӥ|0댤_G2cP 3/gtJƐ,[iyt oҘة~vmvD֣Qxh=y&:} fQf²ڈ<91^%ުzdjՅq4- /p(tlUfȧsECL  Й"ӂkbbI7³~f>DdkfW~ӹ)tpS%6JBnE^PK t=Dflot/examples/series-pie/UT .US&Sux PKt=DT4ao#flot/examples/series-pie/index.htmlUT .US.USux \s6,0=YuorkM%$dHP-e A%Y<3v";pr/_ߋbiVx?tXO?$podzwi~9{:4D%靭J)s_VӣqL"俎 PKf?pMԈgrŪ8/)&Cn-ceG`0T ,@*> sJ@ Ό ? RJ\V49ġѧ!<]*XC7eg=2T4l׵P{mV*)[YƥqMn9LqgƤu$?l;l%4i P8 O6tddq(v31;|B'}GʞL'<-PSJ19P+OGރ7\Fszп+rS_,e  I3xKWōZߤZNAoyTNt*\g"$:<0AG8溄ibn|VqPY-HAyBD#%$usVT]CF_cFZU)qpc]`h"IA^wyd|;8"w7z.bSqv:ayX&R.[S0?.@p, t2xQDz'yV9í:CgZ]6ҙI:`Aá14<ّxC4T|(W*ת=AMP-67ک^hnF{u.m_7:}p}~f޾c+6>^W4o6=fSlyCƈGes=8ͩKD*> )O[~!,.ҼC4 (]إi.:8.c"xﻄu[8П[M.Kh$5.[%t?n D2>q]taÓ VuL'Q/BgNDeB RKV_/}Z%8\ 9:Q=\ry~hڂAwlKL^*~Nv|1xz}mW3,@jb!cOKEN{Aoo/JqvrHK)jDT07YxP[B2@J`3%`BGܨJz'M HTm2.סO=j1>޲>NwoG'T uư+QFHJ fcQԨ/B'g\ۺճO\6v_7u]{آj᧐[i&Cmѻ4~~efئ}O.e=xY^\x``K5*4*xA8o!z؀n0E-Ne\B@BDyMN/2v{ @AeW -CVL3KtmA#U[W Fko 5{UC+mW#?2p*Z|CoGY.߰:TURn$B` m=RHQX5e mXSh< %ҹ_DgqBuxfg{1\H1 =2Ax4-64 mƭT2k̷2Yߠ-,nv+:YĪ*i>۹=Ӯv:ru?֌&*-XK<>`gP @g*s Fd $)T_B@|^L[aW)\e J]^6Ё ^0y(|&'mzQт⪈ tϞ5{KKH6d@X/Cd w//Y ]/QY+Lfh :-&C~k&ánx>]N&1e,RWGG>9Marg߸?q $a K?M. XQмUG3ՃSKX[{ *~\au΁\~}~͜{f.iHv}(GW7BFJ*Sؚd@G3gWi -n+NQD?+w<[3{ T-|eu ox{/ Ç0l}aS1S d/x7_dk7C iEr .\,l{vWz` L8nΔY+7qY@ w=Bj,9v1ejef]A0\she#g`Jn["m6AM?q,]:1LL>gπzujg`&/9dP׌0tH 8cCRTk;UR2م\)FԽ@$ycK܋&s MDsy,{g\^= /@ct(.1(x;A2喝qpIp>KFhJ߲@@cM.^kEU4o?D^{ [d$t]n>epgKY`*yp6g3Dv0Uj +3t90^ø^3v ;0c{'j9dȺ3GcJ,ٕ_J֯x~;R^9E ɓ`-N uilP<΋ulߖ`/zw%y2+p )>i޵x͛-._5j\p8%F=jU_3ݶsU_:drΘBh)ovC;S5tx kZEn8KT/.GpzԷvuuj .+@srLU ~#@2b\{z]\zN9[Ʃ:H (} Ȩ'%C &ef3&mv D)_?bO:X_3h8P ; qKh Bm +쯏?rPeodq\陪|tV M=͑ȥ8e3G 1sAta`~`0S0ۆ >nW)Wu*(c ] , =߬81N 4@I5+5.:lBĠߤEei Bdnr= %5h"H ?|n򘒦bLIS֤杫\\P06#߀ &eu+Q"pLi!?IہCe6iLָ`26+R4?nzƕf%՘@,D*m1BٖsEGqfQcUs(1G% Y\@ugШp^pCZv85E%H=j .+8Lfeq=+! 7o~QZRtuޭ0cW<{Z!6MmugpQ7 fz *!!VxS ptIR0:o.VY Cf+MEٹY'0. K;;vcָo0#;S}D#a*,O9j8}P7Y9I^#s$gX` .P?~^bxL\J ckzۆ.{| 8!SYNkP|T56Bª* eOeG)Ϋ#k ˁ<:MV k2^'/$lf( K t).lsҷV]Mp0 -65PVsǧ2/8:!Bp՟XiKw*k55_Ah_KǸ0<<2}oXػ]nqY9}x+ rj883 @(\"t' ~sLDڍe )MqWhmh}/"7mvR >$|t%^ƠK0W1/09D_fUBgm㥄׼Vύ;SKǼzam`J?{{ DGʧ `ZQ6k3:^.k I魲w )Y%mur;Ԝ 9 gF s9TQ@NdjiSQ\}UvvmmAW b9Bn軒m Iv^d}m]2;3~uKDD `FFkk# x?ygD|$):jsL{d +3؏D<5G]U{vo) uM܈JؒI g 3S$tKj~u8{fp(JƭQf9u'I `N(\@8i=T}+Y2Y[tjCsД̦F1">KsN d9xNu"pҬ7Z@Â2WbWap!J]v;qCf w0v Bױg%c(NSr})̄}Z٩ E^uSsfY%\>V`!gj6Z~: ׅM[kfa EavdVf _ZA㮟c ,Ta~xz|]C94N-~o K4w+-`H+ '' )c3x+PZs";H3׆ȕ4/MlX+b261b`e![0 mf ye)S5: T$_#B_^%ػO6a4@B%1S֊ΰV^mTYa6Z sLK%wAoAP@&N?(9K)Dgj,ՔN]b:e"p9G%WțO$:G]:e-&ަ/.UN+~Ec6Σw70]ʛvקgyPK t=Dflot/examples/series-toggle/UT .US&Sux PKt=D@x&flot/examples/series-toggle/index.htmlUT .US.USux oۺv V+%9ۂuEbJF$:1ߑD%oXGW/o#ڈm|%r|yWW请W9!v {zzr۴k'׉̅[YdXd[.s۾|p.ZZo;\KB;G{'4"JQ埫Flx@z]]^ZЦ u=ky9ՅӉ4l8G? w U(_f]ޖ;*Vl G,] 9፻-k y2{{\rqy{8fuFoLMW:eSOOѿaZT0`;tmwYIžjo7j.HdHӔϐSԧS($d?HI!!|x 8NhQ)8N X4H} ^NPɡ8@$Ń $>e`O⤗O{  s%鯺5avQ80",(JԈ4"8(-E$F H?(FhUH(;0\n"i`}x{ !r$<alQC-|Z$#SlHF!A$dG1$IԐ$1M$q$! I"}.iQLАJĐz>0SX#knY}x/}kL%S蘼F(1L(bL S85L Nihb) qYLdD,ר-|>c᣾])o7bbEqb(R,}!A`E}`kρ|PlEnv88W7{ҿW7tlI DjUHcv2|>ڙۉ#d/O >#0bBjER _ZE$}$I|8˛/_3-O]v怜sXU_R]Bo4']Y*I'7! j-0/D$~.@.jV+ )&u^í~W/C_Ij9<ýя~? mkc/tfoPK t=Dflot/examples/series-types/UT .US&Sux PKt=DĀ S%flot/examples/series-types/index.htmlUT .US.USux Umo6 Wr#~ͲX6:) ]0HLk;vc7``w1:Or YWc uǔ^L.5V ̘jTs:JmvjDl$dt٘5%FM}%C2 &7$35)Ͱ2ipF,&磏4p-ʜs+5XQAl. S<0|c (6k d7``*R K8"+QY1wl\pa7U\[Y+BDԡFHgA`}z_cMQ&5xiUFkw 4LA҆!LgtS1Mힵ'}h4vXV:‡d'x۱ӖݙӞC{C|hwg(w_Oۈ>Ky[^O;h_A'ħ/&GXȅ [z]7a#9y&+r̰s<1ujۋt&W`T}HEox>&v[(y[JQ{m'?p[P-YlqGpvMj6?+5vFFg̺f4^.y_lujYr)1e F*pDX*`'ߔA 7`Z|kIr!{r: eЪfDH\DlQowKec vzZ^s)Y"^E&@V2T0Vf@hwl?MMBfwyMΣ¼D{( le0kj81@hTV@m 2k`ȓ!6pKM-jWʤJj8:e\X4J`u]ۧtXKBnbm*يy똄7:Um]&tk1B[7"#zGiƦ6d7XiHnOQ˵8x>0N+Re?,#SIWɵt¤~RQȋ}sMG(u `W c}n߱f}}j-A[)QHv pdqy+,u4iUґPKt=DR#x/flot/examples/shared/jquery-ui/jquery-ui.min.jsUT .US.USux ;kw۶+$lCV0%5ކ Ɖ7qnGU}h ʀ q\I}g Av/`07o`s8hOOo2q8LB뙘9tbo[Yd́ezXY`j|?BӜKIż#%SE.UygLdl9?|`QÍ{ "|LUGQN%-<r^,+yq )JT$IR.0DEn-[l]ݪuܦk2@&, fdHȔv dqb]ی,Sma[y4eyPcd3$<&mEppW6fOk-*g*>pp?,t>~'3"m%(Ѡ$ȒL]ɗ;< JI?f7Fw\wҍ퍉mBgp"8:>oϏ?ГWwӓ7^ x;>8i{?G'WG''pPAtSh }k8k{ۣKh{F/yzq|yy?}J/Nߞ ۳=fOG/gۅE ȵZYźM?RP{E'5Sdt_V]"@f @DtH.5TZ׫{D)n`\6Sr7G%pvpl ?ʋ^ e ^grUa\ѓ$uv?C×oD<5m-+yG^[C>H#N/}MQćU3`';癘OS|qr &[tؘF!lttp l"4E;|w],ؙUC3Áu6ncNp̓-{6tF>nI 8UBVޱ98 wnE5@ :a9USShou۰ŢSܜg*/ޛnapI&88)Cϗ02s.{%?1ipץP:Cû?dZjPj.pqCzAzjEYfϺ0ڱD2-r[xB._JnQs2p!,ީ~4Lowv#l 4Y`jc2T n?'mHFG֟QƤl/Э|M;q6Ajr?`I"ʸ(k>юrxwF8I-RtI3hUr:GLY"f@qi"tی䗻hBd@M R:U,b*L>" q*÷G/m$N@-Z8r.>[0}ր [ "KhB#־L:a^ 0ЊT SKh* 55l§N@/y Ѻ@hxA;Q- A¢nf>5xP9;pbV^ƠuC|!*snxzEr5@S0O4Z\2i}`̇v*ҋ"-&lR` ɦaߤ7wBI8>(J1.V)ƥ p,`^lp"A0nV +uVGDL mV&^x"+ͼ"Ah6j.Lb%n)s"XA3B's)NB4[FGe6V!Rpjd !bٹeRγ'zV\.pAiQ3,NlAnvH~;w6MZc`_ݹzMTA~ [8\Yn'T5OcdجyB10rM[f]Q+r/h~h,Y; >0c-`ʇ$A (kxBy8^6sXb7:x<ux Ԗ ~Ҕ~О]C52wVyW e%FPh%aF%?Q탱xC!aFgQ 8OVXo>gˆR]s7p8* ܝibu(&^˵Ys92&#QFc|&cmU3#na˝hƚ37_6@x&Z\:gS;0)BJ~-^\ܬKv4$8HkeIGJa<q_8s@n)Hs 0"Y+#LcM)Oj+{tJ)K2I%!iҾR˰k`к ލ"AIma%hudR^KM}~# +hv:Zy! Z]LyxhVX6Vu7Eaoָ+ȍ_e˓ӑyV 1sV>w[=(zUh6Y3=ptfv ^եtj`G5sP';}W 'yZv;* ~M90zS|H U| SڱD#"U}{ RjkHesu2JӛH'^w@%!p#mɵ8U#2cP={k!S߯ˉk ǜM}g,ʜ4|TyPFwK>pެud=[Wn,Q˭5dVTՁfXÌk|`>-*Z.-7 "׭V-{m ʐ~cB4juq BO~H3:d?s3*oLNm(#eڭ_1ԋ+b !4>Q0[[jl1wLOe2V7eY*-^BT'. V?SC㝹(őzn˟07) }7KRe1aڢcd5DgkT jVƅt-6ff(#v>pKUjy\ZwkYh= bsU#R=epm/;kIB,E §{sv$+K"2:G,Ugm Zկ&&fwbGcKHxR̐'}+}UpJmWj` /ۀV-$TFtJ-Se@YP/i\JW% .38W`_ mEGfzx7Tv-g 907/o=墻|b6T.5`vl5le{d{C3+ ,+Ȯ4[Uhyuzݽ˺[YUyg皉,ܒۻ JTH#}kxm{i=骫=5<e=R^,"Y[DxaLI> +:ByzSB7ȏ 1;<e:gj%:wh; Đ3c mo4Cۆc l\cnPngw[l6Aq|ɤЊ Q9} xPgOqWlAl>8 +!Sܮ-!:\lۑ6%㇅8"myL 9!,AFВ)v`uuWu=eJHZ+1X1!nXjw'(,|pɨErf9:`>rq83 q̬{U 6 &  =nXBEw+Go&n~mp<eX&=+H₞}|7-ȉ+a),N;lR\48DSnǠ?ׅ@ 6 .#Hl::!n=e-_~[7;qP3k1vlYCаAS)P3"`)NguTɱ!!$2 ",{oDej gAUw*^vgxc8Ko?ko̮{'Z r FKnOB4 4ףm>/m6yn*%.qf: @JJxWX ʾ̷> ƾ'Ro6"YrY+uPUʽjGlBg҂rZ  Ppd-xn?}99r:)u7WQ@WW b0XnslgPAf2WQ\G ;UBgJі xCў~SKnڔ{FηK9;Xz[k*qPh!1s4c T rެj y8weyNb \ \ ¯>t;gr܍p{XbfÒNz4"9sJ=1 k߹@)k!tN ]8 ڍNJ.߯ej ijkرa$g򺸟>Kl6jesO#ahDG~T˒Z*mT#CZr_c.l= )33'.JflV@ fQuBCz7"0hK<%2嫵-Lᛟ A>n5Qv擆Ya p7#wph"ٕa]w^;/ 8rfC:6}P~/]4Sᄿec2zxIя^YFِL!^xG ~|א ӗ8sIf.͏Y>#>UNn +h¬O|xy.Գ^BzC4wf^͑2|QB#ʺ^=|=BOepmc!)NY>([n0XC*Ppұ2E nmKŦ ~I(0lِCzGU|f}uqKW=5t=t\͆}Cq0Y66 bL\xг ufH8Юhp3j:m [ϋ,vg郕Y]1{^Gn2Ѥ4czpp:RGC:1QbR;&Q BaZݤ՗'B o#*RSѸd"a`@6$Lee%IYFHm]B.?42YƝ5Κ7U쌉-JQ29TYP*<2jbx0=/lDf]L8 W>zFzȭԺyy hXN;lu)a8/Tv 7s8-[wP$ʫl(z7j@9U[T[rʩ&QNޖ]rQ\q]oie/>3/>ݑ, l Ndkl%󍌼~iY~'A"~Dd{{B|0Z̪ȨKWD鴩dC{0DO(KrjIFE֐bڈ'7Ӛ%'82Z~=Z;{ k>,1dģу$=IXI7:D7 mXڏ*$r[z2BKOXUeƕyscvAp X ro8Iロ }^zni J?C8 .^uehRb'2ec1? 4-4 7šB)]kC,RC{O5wf f6b]npuf8T6 Ӡ:M~f|`A?.#S}Ï8 -m0NvjGӊ11iStoRDPf\dS}(G@cVv9n!~,Gk?pXC9034$cXz zui0*ʕ*jjذULѲ "j UKm0 - dU}:qP2_Up߽;ϣayU!d=MDN,b@o4:O$Hy=R+@?@" !ci u떢\$3ʣ@)q}vĕw 10^Uɐ #pq6,tKO6BUҠ>/P#ߏ3U~b?88ķ ~ir- Pv3c3kkD` lz5oHדȃoe=Ae-KЦPK t=Dflot/examples/stacking/UT .US&Sux PKt=D5B%o !flot/examples/stacking/index.htmlUT .US.USux VO69:MZ@۩M:Ӑq: I9i&=)%LMB8~_>\t Yc 8<< :xGpǧ 18WU:dzc}kxfdX]ͧ;A`u _XVUf0[׌@w)18 d%U1 i.j04<THIŬ52 (&R%cZ^k`w+^0 N4љAyChK ;OZe߅ 5тW-$&Wyq=X02g"_#xjESe*(TA>'-8\Fc?S(]W-ʄ)#E\.8{kyky][tčQ s{l,fKadbQ65^%7Em:lۋ"$ojA3VJ3EpWtQ6Lq~>Ⱦ ]5 .x{M/zhU_Y/yn1 [ם\>;^H|OI1FVegw !kŢZ%'06^d;3@,O~vG1T|msE#lk`ī_!j҃z;{;v8yd&̒)miZ5#0fan05!qyAG*u%ɍ]Krʑ )yvvK3ANIr`S^OT1mق-mSWq6;*kyՇlt띥kfxsfE#Zq]ڌ\#n$P*/'8<+BL,,,Xǟ-P+hlxU7TQ6tm:N%q+B6ETR٦y5L%ֵ9Zyim8.#88B08 jTPK t=Dflot/examples/symbols/UT .US&Sux PKt=DMDpe$ flot/examples/symbols/index.htmlUT .US.USux UmO#7~NIɮ(DNEԣ*g"~c;Ps|ii3337g˿/Nt?;;I(kB1~ .'_ ҹ|Smf:#srx+2:Y%ON]+Gdk'j\.A q{CKfp!FtJ?+U-V6Q0%[((F$MX!ZFnRG[$('Ǚ͍l(VZ6C gQK5yBYuzN2QlJ\I=K?7w034mCaV]hI]w{f9E ҵ\{f%,z$A8;t t=Bz?>Ύ;+FvC?CJ|usڴ^= _+S+Z#i"1µ{ayǜ]<1InzCepr!H.Mpo${d{2d.Yk`3Wޛ\hPwi%?5Ԋ Ch? #~N[8ӊ~ep\HD+=;U"RVe/D)|\) >Z~3p: 0 }<^`uIx לrX%M5_˸G i'+ϛ|(vDtL+{k:"TW:k_n_ $fN|+\XąbBT.A4kK3οF .ÃRS&qj7] |ʗ2pכT|k4&d]'a7|7=Op3#[e49PK t=Dflot/examples/threshold/UT .US&Sux PKt=D^W"flot/examples/threshold/index.htmlUT .US.USux Umo6 tbQrm# .|`$bB*yk ;Jrl+a`[5Ү#gUM+QX4UT ALႎz"QrAt߷/y WjM{%͂"%~6{|TXB쁏ׄME&eCoA.P)a{ʌ6v ds9ISViAf5{'I;UtV4!~zzFvFeWB*ٵF;xlM<*{~m/䵕K+YFcⷝBJ[pnQr[mB: ~ :/ަe.K XJ|b~cUs@Ӫ cPVo]Ri@Cֺ28|rL·U.\ẏnLMdMsOSbx'UFGA{l9I3-\.L䵂AnvI簫тm m}^yG$o4@k D]5pT2h+4'DYmg6r@(qh4-ռE߮JЍtC|aU rF i;bBX!tt=4 n걡q_=}ƽ&?D'|O^6^[_xtmdt7wi )x]wPK t=Dflot/examples/tracking/UT .US&Sux PKt=D& !flot/examples/tracking/index.htmlUT .US.USux WmoF]jtr/b/x5`wfKv^<3緟n_>A6 |㷇]͍No\{}ʆO+O~r*/R=9 HFE3+pŀ]۱}#SSNV|t1 ƥZD ɻD*۳MbӜ"]Q]"Gs۞ †'cP bΕ yɀ]w&(w|a.2 KW%[mDh<56"֘$$84˹Rgyu?ĺ\EDwI^79;.eJ7X[C!RlEz5KCj?_>, ,bg&C#:035J'Op)KXcD<0( b iklʳz=۶,GKJٲ'ħ5y.h<‰8"!LnIsAcL{hEԨc9[$܄zJ8_5%K ~t^< {a!Fլ ⴖ6YNZ߇؃9D I "^*X X.4" GŢp.e>;#2v c*6\DLQȝ 5ÂJ+Q^ ҈hڨu.XȨ 8D4IIֶx09"݉}oq# Vc;钖eڽ;qh+&u6 Ye5u6D>gu{Js,%fJ`\IY~ eΒ;QsSOS4ːaU 9I2(%,,-BYTFW&heN"#0f:-}zZcjQaodVtë`C<[`X?%Xc7 |_PK t=Dflot/examples/visitors/UT .US&Sux PKt=D>d[!flot/examples/visitors/index.htmlUT .US.USux Xm۶, u'|n=gu4t`aS$CBS]פ|ݟ\gy߇W5\?sSJ.=p8mwwO͎^vb-B峕ΊgՎKFa//c6OR;'u={Ydr"_FlV_^ȦWJԟHͅLu;Յ#%!x|RIN޼&_wbv϶`3>p Z֬w'j#$By4 e!9ʄ( G&(нEebhLbmc2ĢI*27GdoQ%-F-$E*=4-`# B<P%m$hJ$BĘ[( HCpb%C[u[4HQp; Ca*|h<[_8G:sbMQ%bTI8zȣp,?E!0\!TE[Nlx!lSd \.[dwFoJOd|TI |%ѽ&ؓBm0ɭ7I!(HSss)L`xЂwƦTu: HV򜜝 tL&Vw1'?u藡 %Zrբj矠쌀h >6eY?ezX <繛+t+w؃ML/ gۨ(~RT/)PEp nz9#ԟoEez kb@L%W%!ES- &G\-i fǤXJIMRFBɾ=0VP'SƬĖm}9Lt53tnIP7@aid2 _D(l-@*.{j`ԃ SEkZ%Ԥ|I #Χk%5Ʊ!2m(O|Tmb;mpՏصk^6U;N!iyw/@',f'}6Awc9>L9,䭇;ЈI hdQ f;8k37J{(˺^Uܙ=ok|PK t=Dflot/examples/zooming/UT .US&Sux PKt=Dx+d flot/examples/zooming/index.htmlUT .US.USux Wmo6tbKv-h .!|`$b"*IRII!6;_y~:=9y{wtq]|>}?pbV+wr1.4zߓJ@ 閯epT`ˉsSESջ(2@`WG\{cb"$UzmD1 WpyP9/4b<9KggubA-qn &G1єAhXpr  $$- oɒXᆅX7!$uoщY}EӐE׽~]PQlzaV#,iZVU}[[vH ݁{<H 24̨:"AaZ!Lz2? mwiL丟`5~v>.;eB ]vEs1&q S{C8W.xL>L !Fe2D$ ;˪`%@/T6]zw˲W:sR 1uw/.HTVݍoc/@qȄQHIb ۚpM\T$|>> 4y[MpX}ރnuURZ-2& ˜t>Ee9/Z- <g'E쳔KF 4ɯ,&uDx@/b  yN #ak%9 b( {|)Q\PA೜:>mDBs%4!qPs f1_aQߗU3'+r i2odRTN"_Eo`(r6$5PAxQuL3AQ !ԱCRNJP>ҔD䂼<ןSXC1kX4+XxWL"o} $s%p1#If!3J,: 5?"] .N_CA q9Ohӈ޲z{ Wo߹;hոIy^ 7W1ZNE,{& L1ߖ GQQ9IRiL:aV {؂ڕ|p6'a?0W!$f+@S?ifŁpt@ #֫)AE泏X]EI5z*$9FQ,yB{(듴$)ՙDD\y4 mY@^@B@@܁ n MiDJ'2j"bTO *n#>"VK&:C+@0JQ`W7x޻J,.(dȊM3&Ol+%fG}u@V`+.anW\. StI"nMJTʣL qp(crx4ch(O&%,(| kz9,;0c-akC׬rSsX Z;,AlhM`$U'֨٭D+P;n!Ssw0մ_(5Wْ][?F} 28+D4;/8B: ^|6S`%H F)[8 jFz\NtWW`]#Rv[c{kEV_RS<jN 5"H8@m΂v8 pyWgY|^#+hq<>jם^KO{bhEWq"> p> 3y|S{T)*lMk0,S 9l+cٍ:a(Qg ]vU  Y5M63* d`笜DԼ48a #'D-re7  +k"*W4x ~c upA`"D}VJ.I5 AeqۢW2JMhD!oe)2+XX:]Wnst@TBUU~Ѐn:eVRbI ߳OsČzo*cڠPwK Sh3Xdxm#8T\q8moPXR̬0WKH"b=C,ݶT*λ8fdṭrsg@tcߪqpրoLji,L9G zA O[b $\Vrx(H{b}tԅ(\ CxdVpvXnro ~+Kmp%KBH-YJB~Kz! 1,=Qw_<}^]+2|BJ Op1FRGtsy_oR"Bk:)Pg*:dj lޒԙs K\5 {{8֫WJ:}31Pm0X0GtW-{0 L(eLu;e݌2{z1 yࣀKl/]:̻CN2vBhOm3Qɹ:w \,<*9)Z훽[mI]S/݉ww-:A‹gSj- C/Ng#q6gSJٛ gIY~AypAN]}KS*tPo&lK]ck0+v>b}8\XRCLhN5ŋ43Rm׭ɚA!?lt49O(0:q]wrA䩸 \X';=k_j-OÈǾ"'\ǀ,G`M W;ԫEnV Vh0ypϵQzteF Swq0/ƚtR.Wccީ|ڛN,pyie\3wf}>hhQ!TZoW)cwb?6vQ$K]&KDm zk+ UqEQYuzz-P|Y$idh5R x`Ka,h&T[.BT S^O' Z)8arAk*:ǧ6 {ؔQ2'Sٞu/xLOۆ }l2G]Ґ3;t,ˍ-hg3r !K%ÁU0.JOP% Di9hw ]51le `ӑuA4V7ƽY1#O7P%{Hn{h!}qE}wWeKŬ t2xL t!d0ې Ɣ UvIe=mO!@X#!7FqdžڵMK;B<nh`pz̞猅=>Lme6B orT.mQVf|1?(jD[ *+hWH`Rl=xtҞ*@GI ɨ?NOZVorU0*x0阾 Ტ=:QvNOxVp8<3Ԩ=fA#SLGnt )ωg6t&5LvLvewH`¬t:01!&5A,HC(bs ڦ_%4 H܉6R¨L\h8:5v;A]Vq{c. d؞h '|}mԞnܘG3|CMw920S|I,~{<l]VjT2?ZҠ[fHldn¨av;wkL`Ŵ<)e-˝OjGFN15[-eFÙȬBbf=4SY<"B^޾~1{ct._$EEx%؁YZ$GNI\s @H"I`)"ʊY^WMp$ rU? }|@`.M׀}`쒿]c|n'a^?j Fk嵎 =NyifnexR2ܺ:!"v{ύNHZ?z Du2 o8xYڡaݮ5BO4TKPi{ovI~ m`yp !J6dӹk+A1skeaX#d{ pa,T}W̅UPӢ@O "~2v Xw5qZJT<.t&wzUs@QԊHiy('^b(ەEi.,-؈/gRm--Db6fw} E[GĘVMR-2Ra>q AFL4936/_h56fӈRnzэ2OѦ)qsG:;;_&CcHpoAVyf_`+sEe8MK[ZzCK 66Z;2dNe2,a=[RinVV܃U"NbL=iLc\1t,KW{V.B즃 i'CE^()n2*0PT 򫱷S8Ś92?D1.Y:iKlQ}27ax b&4U4"fL`Sl)_5>03Pv'cX~ֺ>TRUeH]k!*LkFY a^DvZc_v;kilh@fh>'LY{XuЛSj@1w@˦H1Hei?ǑxDD~شY;#&DTX./.||N]G帜ޥuRLکKBh kit@PH&8ie՗P'(E's75.F$ rk0:PWn/AtDe4.o˨`2K:C8׿AL(MA;pydGEU 9k,/H#xlډ-8AÀGЦ1WTC^'&.t E=줦>zCWpR<(œ)&M03G<]~VbZf"SXLMIGq=K%w8Z]M`h(RQ ]8u8IV-pf۹޽5mn{ۧX%zumo}'&ʛUpFfC"U蛌KpX&$a?&rejғoiUm3یk'ㇵp"L^֎f]˺{nx~)ncmN [FQ,  I-a (ةYPxm"r,̥tTRK9^p5ZOvRˬʖtQq&/R{gF xf>oAVuk /]Doԗc泿6ZQnW7ԵW˭ =(2 :ŋh8BFmcy7-fGݢ"o4j+Yv]m wrvjd443EI)HtH2jsX ꩁt!JctJAnMd3|= CcEjIF1e'2f+ŗTjLY ~ 9iBNxՉ2 &Kx t7Bx^ Е]iPC4^=#oe[ŊC k(jӷNV&ۤę-3xT1eWLXѥZee,>iM-4<΢YFF}p.~NCBy"2y rJBYd%WPe(+*); ~$T٪k:HmW6d.(]3~<{C eU5Ы>4ݫĈn }hǣoo:eQh˜pzgx0=BDL=@ǘ)?`]y~qFJԸ`;RT0̅7iXg}q,S#GfR<|@4`u^RLD&11AC6y'R{t}RT!dedd&ʖ˥DzW2/YìJFsƅ!ZK/]Oqޮ v(+v^w7n®yѾ=6=8`UnvSsW+TMtMmukZ?,e=q_[.W)EzD^togӥ&y*V<ڷyթ7|^"?ܠ!*Ձ`+H':ȼPK/QWY"Qc }őC/_|;.6kTT˵)? DNkIAmsl-rK[G16pi1pTi/?0 {A`qxEb)u,zg@/b/Y^_REB`,2X4>K|\"7"0 9\ͭ<t]aqfe_Rvk.. z 鶫&ԘX|}rr;J`q6JNp%65N,=Ozb,a-AY[pAz7!UMzLЫp8cNz?;wĩB]_f;Av膷J!!T.Opv1{sZK(*&g<ь[#?K]w~sPf1v>pyg'w>>}z{lo'w| 6T:Nw"tX#OW b%Mxբ3WȰ 9OĞ  0,¬4׮}o~ [[ U@1+Et߼Y1$j8':|ƽWSڅq8#95v рV3q 0q\“¼;n6DHh.pt6 >y`p#v;s SRc TFZ$2X6Ȕ!nwN} Ey`{w@"]@p>8;yB9ˋ;>ǜ ;zsAWCvpp|p7ãի7T&ÃɛOh0|kM>훳)nһz뻁`3ǘȮDL*5@N|L54`SR!oIx#+.%̫On2D}!޼-'yۢ2} aIRXPKt=D:@qyrKflot/excanvas.min.jsUT .US.USux Z sF+2#YLJpRz^;䒌|>WKlI-5$eKc߇CU8@hX8|q?#>v9JƜ,6ʵ%O]R~,-<_*?޳O,Yٷ٬[ߑCOy4`35Y}9rl˔ ۹˧ovgbɒ mcĭǒtO:JuKy<ۃˈ'?KV"RHm(bZIC^]1ҺUCaC{uK,ZJ]zw.hLC5U0gIt~|آ$ٟHKj]6˷˪ya(@ ž`u Wm1ǁj|ۺw}h9.?~;jn<_qGA,yuA`{:s`"f׵8ٻ$ݝ2ѻڄ?gT%L>&ȧWX-14 >| ypJ8{d7KE{N6L3V\,WIjbp0_JEsQ"f!k[<=k K6_%S?powcJEtF Z_=[htpH#ᐇ<8Hz3/?Y )s)g/|X&_T "JԂ IFLqV^Kd,pSyOy°AÁK+)C72eor ‘ϭV96$7*v4.H?jVY_<+U/ nq)x#W `"8e%ᗄ_~Zq{ÖaZVG%uAݮ+/ bc?d!I_QCמ=GNW 6"fA "VO_N_wDF-`ܾp$mt=kJШt,柑?(fKNUb@e3Q"6/w&=U'?mǃ5_c0b^O&߶;37'cUOWCL!`lr#gq!^.Olq7f_cCxn9sxEjN:>vE%G«y7%0.Bꭎ5,+4M9)S^uiG  w#i'mu /кjd|)Râ^o(jR2pER.H2S8hC?)s5uERi)f6V [z5QH<]l uW;iӭh$NQ0^4%8tZ} ,ݧ= zDI@}r#8?#Z!_p<<6jy _uѠxNkPxzV~4AgY54EBZNs2/L( Iz= %~< @ $VK#W]v4km#sqh2^>;!um@IVg_#{8jC[WdR`]^ (I qb[mLp2JGdqkAPbRSI~D }+XH"5Rpzׇ㖆eW@c. ?hGs :jЏe:enMݡn az8d;\_۝1?G$z95"R/ pQC1)3NIow;'ZQBCR, &MmDi\A .(14 Q׃V{<0!e^y *bj,` 6kنz euεI`?S߄;Qwߘ HÅA{ 0u24I2(;Nqz*~|A˓ɕiP#V qx248ݒ*G96"Kji6@W]Qg}_Y *dԗPDJ> pc?%dTy3!aK!<ʹXR@z3SWOOR6Q~n2^^ ]E1KL3'd2'-$%X.*q lUe]؊-oee~IofQiN4m*roB)llselqqެ5 ۔SVm|zaibWrlpAXG;#A)f^РmROY:~mxyC[?safd#n䌍FdQ=N|sGR9f'cmx3 мh.4d@FEְB9׳-9 kX&W zUf]9CO\{[]:t.+Gmg t]6wp_ky9T?q5 elJ(y9pxi`pv)GR $FAZ dsz';vb^kɛ1]uҒo{_7v0E>!_FΝ6c`-/O-/^ 8zv#3>}|i_R6ѕVRyRpJ${PbJ8uB=@_0X2<r:l)XO@z GJF {ףUu q AHاrBqhT硵N!*x㡮ǃXK].DAc٩yQ#<$ K,),]*HnϑvLj2<>tq(~:$\׻l`El!;5ԏ$;v ۜ#{W[x`*2fnO (}*1P(uWt)'϶۷oh_{۪7džJÒs,85JO%L7wؽ;m~xXtt/ Dڎ>ɥ0=Wٖ~E˯$@'=쉀VH- d#e>$Q֨KPsVOVcC+graHG3IΌ0Ԛ1v#y"I°]V8 }]S!m/ .%`UKPG*2"׾`KfAx`%e3?'.*ŘGIY9(Kƀk~$p]BBUǂmBD4JAbN*RIYfy })[QavZ}!) ҳW,(K)\G<'<=E!lPvi I*tٯZL%klg/ușT;|ͷoIsI| *!@:^C=@AM??jTVNu2[{I3Q]w9?#sĥrϓ"qE]-wB8Qe VH8iL{5U>rDS T:+I)[-SvҖi $(DGP⃼%4@Si\c/9jʛ6Wi ;mҚdCbh{:j+Ǯwjm`X]2KB뉨X"Mլ>+YDyfMfLnre4ldpY q 6 R e6 exe92X?CF^0ow9'SCfYoaGHK0o0p)n}~b`d~ 31XQ)#Ó}f.PQuKKSDtLҁAojJ=ɪA6W;I+[d HFB>m.W* Ϻ*=VY >U@%Yנ|,5NJ?^#>?a$$i|a^RSNqFձE#Bbgѷ Sf~#YB橈].0g3]i{QM;,x[WJ*C.ZaSҭRlnכ$ X[S`u5DZҖCDA7N"}W~BҠ-Ž=hܩ^衪{ShB==0]>ZFQcu@+ Sgۓ4S٩Xm֫*|X_ڢ˪}%+̯boԠN$[r-_( LExԌC[sqijg2wl>j,sG暽/ʰoSnS˰}}GӛˀuB14\w8A L~Vͅ9ي퐛)7BT)\_M9Gg]ݾ悪)/![1?ZdW?4uibֿnꀃ{K9W2w:(ʚۯŒ& 9U?:]pgzgx((ʌ=˓;~~~)Z#b}RJqA{j7m=,.UK:<sb?3ȯ^ {iIN(td/Uۉ+_@;1HWC[NwutvUr{[ݰ>\}[1l.@7B&'h*FQ vХKE`NҤuDcӂ $ySef.;,|nKǠ\tTыF(.'z`1\@, AZ[ighKd*XuF{P+p2*[| FЏ_2j|a6Q:!NX߆0q\@yeH1իڷvqK;o~p0,ѫm쯾쯶T(]BO8K6] /NM'Uۦ6<c}q|n.bPm"*Ձ[ SAAfQI}䉹ġXcS3VhVW;]#t'%! N>fMD*%7YRp{}C!Sm1dxVN9["Cr-j"B%8P!-^MhmUԔ[L>(qj whM=ܝLmCi  $r*FƵcV߿ | CjZ*ζsޏ?8^'}/3GRCu/$wߜ~w>ϕwV(])-qI;܇ ׬cw8O[BZuͧKjn z<#g齟Oܷ3wQs}2Qg6pLuzxr~huV)':(o -tk6+%$$B!$yaɉ=VVGQv]]rWi3!5۱ukh7Bh 8 PM}nFQ>f4POokTQp3[T֤d[?&GTBHVDWU5~zz ,k mJv<"8z;th_Ⱥ[f7sZ㷑=p8Kj}횜3@),2M>T-}뇻 j~3RNv3+a=0`S. 4N -J|pZH뇔$ O n*phY1=>hO{_g<,ϻM큥๫]p7 r9 " ΐt*AƷ 3^cK07Rl. ̀b"s2Q2*CM`!t§2/ T,_yggֲB*( ;L3MBBaQY6%ƌ<{2 ਪ`/f/p|/<h5U f8Sl %r#CO[CCTh L \Ueyma#HvM.*ZrVm=+D[K3f  ZA(t fX+v!`:FH-}8~-gv dk54خZf:ic# }ÊyayX` i"\dJ`"lG' cT1㻁uZx|bX}zq|Ƽ}=fruGKf߼7ԑ_ >_{~q*Sq\= oE-*zIae"Β4b<2C5Q TtPD0D>@@tz^Y0/YII1K J0iFexV'T!u8 uO Ls-ziKl:S&t͝'Y0c.5t^IQmKn[Jn1q5XeEL DN7V|G+"\|nԽv \Z5j^PeG e1J9'qϫ5'dwH,J 1*\טa޸#xT{YJ\;AG^Ȅ?|~,U.qX&u/!"ˉɪ58305z/H+` !=E*1JqqV TWW`#uoF]Op+h/ʛMh2vEpݠ3 EۋFp7Y3M6 h//MUs\$\MTW/xo`؂77m G{PKt=D)= flot/jquery.colorhelpers.min.jsUT .US.USux Vko6+b̸z؉cU  }thY5%zuw${vu"⹗s/!Ş7eR缴jpEqX% 3ck".C0q˰l{$SWӴJps.lɕNOYY2LD|E0 Q^aEAXH*hxoYQ:n6hY"mk0N`h8~yi[B Y;*&GYUӯH)VvxMXCqA%](=aMaNM38xEDE)k0&cy"T8nä 3vQb+a#ldwV"Y)}<CHウ{vYVp|:֐=Ȏ0y,jgݏ%@}5=ߑ#lQV>pɘu=oMFᦔ;?QYflWy4x} gcC.O1t@I;.ʤ7xqOԃQF*vM5a" ԴK>6D;x ~bPKt=De= %flot/jquery.flot.canvas.jsUT .US.USux ko7+Xhzvz'-R7Խ@[8ƁRR%w-)=2"3yϬoJSUu%fƊʵBPZv̄ 4JLeu/]띙P89󋷯 qQ*V6֩*SU9U*%LίDˀ]XYS4STZ )!7ډRNT+\UE&xm{*W 8RvRsd \ iu%Darr3Ċdk]/OPm+l&Ϝp5Cڢ59aɐ%LWjUʩW#X]cA:5ltz]Z֊'N6d_Ǭ{`H[פȧOp@0+˨'1UyIրEfDwS XRR[!jo= μB?(p"*5,9V7\C4˯RplcOmP@́>_şAJVjۨ 21W:f̯( 3 Ū6vBuEFI>/VǾv*.&Ew!b Ja&t Ga>c񜆭b[]˪fɒ-4ӚS`b5D4e!n!p,(lb9z艑M\$ ߑ81]j9 "SQI@,D©f+w"@1K a -yLe)HJ 2k<r ZW: 4`3/ nl@tC%nҽQp,. `][ԞgMKi@y詘drf),!ԗB.R(z&bR>OS(' (k Aߖ ͘ZʮޖSZtO2aGG$ev }s ?Zb$~ŏH c㉅®o$~O;b$^Y+x*#%Ɣ1oo Hy:wU!>z꿠ӏ[1B1HbMWc!C T)iO!'"Q$aC蜝7M$Gm5 s*}IJPk?U&`X0rwC6+HfGDۑy[uֶ8T)pel_S&bMQ)K&5cJ[(Ae'Fz̸[%`2Vr,aj/t͖|:r+5\ ?hF]^&Ҋ5Fùwˢj05@h ,9Lt֜@GW6K]nYin%(B $8ƠX?Lj!LI$5Q⇰tޝ" q+t} *t+'S.c٥rE؄D2D>׫; } n|2"jtyQ/SoIEjQP \%i}k_XqltB}*_'~UMjC_pSˉ3eSس;^0stW"O|oQylbah|(?  nȃa*Hq17-}~+®whFPމ y'B ߇ TM9p7FxᰳQ2Fhd9# ?M'u)N@w0gG>  ␏'JjkI;`X(I) q8Wp.[zڕj">VhF C8 QkI] PRhoGeXmLhm ܚf4qác@noߓj:LBǢj#~NŴgx!r<4qٔ&qrčbj΃Bb k8l47 <ԊbT ղjqopX7WpZ (GtVa gိ:9{x=,J_`~ag+{ݷ}oW* `={!vgcx/]Xnm?b~]c7!~mSz5‰w^K,egԬދc*`ˬk,0Ӧv~3%o>q!jCO_|y7{> )0t /I|$K r>D>6|jTq:Dnxz,]!x+٠hJ#AߚlQ8O"Iڔ3`Vq)cbDl9_˩/cd=a. ^I|G;LkDdǭaWzsۻ#?_.׿볫ˑ֞ON *+/CEi> 3(Xy S\I˺7BݓG?bUa9_}%9hˠ䆘FS!jQXe,Kwأ&Ǚ^`FKKJWKyg͙; Z.mqi\w#BNt`3,H tsX햰$a^| H"I6#{ eN)SB _Bq$~KC/Wn\8lY?$/qC^EtŸ+(ɸ׉nH|'z!wа܋}=?OwCW Idm_+IAyD-"#z*c `y~Q{n(qPK@Dtff|qflot/jquery.flot.canvas.min.jsUT 2US2USux n6P ״ZHm.MEZtoQ0m3+KI'VU{9Cu(ꃥypf8oMygJ+T>*Jo+鏭P%2ϼic]xrr.ƗӋ<%}*;UZdɝ\LfPY GVܻIf cugz 4^ٝ(zӈ)|X@EqHhg:t]m*} te 7j ĥWF>Mh(e_veG۲Zcw߶Nq˥&W/ VaAGS̉ky|7~mc|S!rۄRHG]?L27YQ!,mM`T 57d3-#n[% /=nӞawnc4,z`WZ]F›ɑYtrrdnxkUf _9E%MRwʰAPzs}R FaL.G:KX\tW% =/|9wꀁpz,_BX 'v)]9fim1;?TK[E]\9*~FbٸGe} `Ckk3q~al97wc Q式T'MVMzQ_>xmqz坅XGE]%hi5O|Wh>mR /©o W4PKt=Du>iflot/jquery.flot.categories.jsUT .US.USux X[6~~7hQ|gfhHVl+{!u,l}M4Kb/S23-κr^\ʤ{2f~8e/߾d3lHr[$[V$[1}m.%F\.4^~lY9^gl5ydz9A G:Tʘ"%OrEl2I mN2UQ^hۋDdu۸DIbd,)Gb3bs,gaK 3*Cjnײ1J(si?au$# ҙk\YR97g``4mL (Wxgܢ`ED1ˎJ  Z-8؄ wl7R'aQlV щ Q7mVgEto{+ϑg5j>MiΧ[NIEˬy,AtYf3?FdB^>|] m[I4JfQu!wLhBiy[!{*WH:(F 8Íd7rWeu}ǛG"nQlɞ> 7UVĤ5"٩HFtP-pE$DT-s'L{$g8HE8%YԾ[GژZCީj0dOYSߴ o_f XQf z;w}9CBőXcp T@:άR`Na2C7зv_ר ~.:VY闁w"ms_ d`Эlvwz6;xRhs4]fL5h4ϗ>d~e`hKZȑAyz+5HW ŗUc"_b,FO;4ɳ݆n:.ѡséN7CMvOLZ'XFrNO8fK|VA.KIm $\r8i@{ϧ.icf9Ў;Q)QdO`PKsWk'eW#Au pm-)^&ZECi#iH}61<6u;+ PX6`Ն^Kxܧ~Gy^7?Ws!8_};]&RuJ}D=:pݽV^w*sZMߴæ:iwajvQ?or7zPm0b6 xPK @DR& "flot/jquery.flot.categories.min.jsUT 2US2USux Vn6SF` VX H!ElCAL\)R#)Պw/%PϨD2$W^NRmf?|~ю,Y{_,Uڇ  f'aC;"upA\&^7 b)DB9a  V`s?ڂN.KpܹչNND9{VXEA쀆bM_1Q*?9fFdR޶=']YeAch Ս&,Aųf]C-I+twy;oqFqf TNº 8|l>ucl]D *PBMt[(ic$4XR=( e^ `ڜ!?R:\f )4 3})Z]@;^J+DKcesZd--wʟԥnkͶi#Sst?m R=+p4Kt&QxPf4|βu: ʜɔ6=DM8?tؿ7FFu"(fw +` qgHѹCz=סUi! Y7`(Ë3}-p6n@|wPKt=D%{+flot/jquery.flot.crosshair.jsUT .US.USux XmoF  s;A1 EuH-C?VS"ɳݒN<<$r^$@XZgG>V2瑈#D%DN*}j|y]o"nlj6^.o~BX&nDRMH ܾ| ]FuoY3i3שsV;OVrHH&/;{)w tQ/xJ&mەĵ㼑o(h Iᴭr̰Tb 2&D:a N`2H6q'h p skVD:ʈ #JNr +m"&b^Rxr Z!IY wd6ß̛xJ QPC7a&P8IIAaUVd+5ltH\g{.:T Çߵey )2bfl7pZ X CIYpckI+yHkÞ'(P)#R2W;<#ѶX&V(eGqq :VAJJ~cwrlCԜx%Kh- iܪX"w&Tjif59$>6h!1l++?( 5A"Ar(xl3dj`4"qSP4+ԛ/b,"[ߟbAb#s0i)< fo6H#jKMN`bOYkUS6u6L06DŽ./Qcͭ* #+Ix-F <&>m Onl L}kiLajzdSq[bM؋LUl1`^)]/mH`*Ja`t~4 07}zL;;swe[Ck^?7,,XfUl\-.f (HV .ut!(e\ﯝz' ]k:Gd~)Q#q&N&OU&V<݊Tr5$iaYU㪌N"I}s &_KKDܖ}󵛘.WдreBi'# ;Np0z4Fl+-UzVFԲ0 vD=Zjc-SZZs4[i}X12{DZ`& PGq؟x[ejsϻL^cUW=g@@EOXUq3JV_/iLt7"?|zN'OZf|>Vj٦}{qᶚ!x S#\xCLeT֫z_B3 D_/*O-m,jwY_ CG)gF>6I;.QvB#$JCM 'Nr;Q߻ !;rhr*vY XG] JwS=lw#^<һ W{"n&AIU3 hf$͂k8dwޔ"a4j= ;& 3 I͇uwVn:}{>v5<J43nLHс~m%lt5EP(&4gpⴇ ۧҤ}y~HQ~$~{yl?DJy Jq|~ԲGˈltMXp)հV=:~I{65QݨGm&Wߊ:Lq Hv[#PKt=Dkj F1flot/jquery.flot.errorbars.jsUT .US.USux Z{o#8K vM9$Mr XQ+ E$eM;3CRrwe{1{_'Sś(ekZQr2\x0xfUݭJ#Nz~1޼dob &/d2Brd!s(W~~bՌ~y%lLX[(J',}$(Mx2 E<4y` ̥(㼂w\F8p#tPb!L׃UT8NT0(J7?GXY%e1SHNW-H9FF(v8L"RٮpEP'(a.Ea9#(j. {K﷢\ GWI#`H3~*{5ׇ;`v5tӮE$@EÌ-q1ӺU+A2BC Z{^ʣC,7qOW2l%1>"Q[,@-@*+ٳd8V& 6e] x6d:Gyt֎ujrt>4Yo6%l%2\麭-`X1sl׵n&|p8uRf vgUgHvYVu! 1y7Ǯ?qlohK=\ om#(މ?0,gbd-1|+qF\<3`B$n%PY=v8i~T0rPP׭u$<,ylWLvkEk5\|:59a|B{$GH>Ngb5WޫzP(=kw:ulEF=s$Q o ck.\?OpȕSj6ߪ=*'"fLMO!#2RBtJD.6nhaT[51%n`K57[1^:Ы>u45#sS#EmƦh-="]ɧ-^qFNHGZʧ\ƅ'*Dr')+ DHln'VѲҋ:gv;@7V^ fm ?rqh f.eM]x׹Eivz(q&;2áܶ “8kz-ܵ\R<^ ITVd)}P^֝2$e\qEő_Z<]QɧUb4.BgGMCWYcܕ+fA"6f<l&8oHë& c'O5VJJ`O Z)IЯbw{5&_I'\^HDg4 O4]H4_ 4_D(t)Q<_f]Ҩͬ3AXPYwJB}Reu˪馤^tKMC\ʓ!91LojPj1N7*͆I%,vѐܱ ЮЁ==*=,Q#E:CkګO%sP}hA4$5ߞ9t/0eg 0#`&j}zL%# Fm[u{PZǖ\aE;Wbb?kr<>AOMrطr^45J,d\>v6$JhgbhdJc65 jnرjW ffy(b16% b9<{mIh7]ڵGدbqGjɇ#t}A~a{*̦?n1O)/F&p@SI{5ws1lt?yQ.>] ll[m'v>?:k҆]O^x{3uBeJ{rcB]P bX G\ 4KEQW^TmJTu>_7.!}-%56E d]L2F馺 nJ>t.2ج$Λ&\ޟhPGйdaSCЇgiccڳNy5ت5QzN~Gme'TdFߢ(%JG"b'4c6474>˪z|2uhQpmVTWj #UQ=h9^9Ez7bDv XThuD,y3]JB/kBk&cY=zbݳv^39x-c*`d`7І( n^J˦\$ݐZn(t4s=KfD5 ,aDQq>п ė|[{nSb(ӼWQʕ]'DESO6g<Ux̄yﴴ]娹n^tjIpbY`gDRhnd^PK1@D<M!flot/jquery.flot.errorbars.min.jsUT 2US2USux Xo6B1@v:l@[al3VY(9f"pkZX{D !"Ls+<{+ "u7\z" ?OIZ~[±FWV/wnx݆ g|im%V7A݋g&^`þpvT2qlK0ɅH<8D+`qlldzs.hIS.~ REɶ6[$Q"h(e!V7 ^岕dC9[l !]xgӚK$W<߈ؓ쭃ܟq.6ś  &|ەXfd#=8|~o&ea7e\HgGtӨezPݩSW:S8!SN*zLABB/򐅴-I*&zPϋ$ UtϿZuJM$igbidO(wja /.|ȨMG 5Z3؁Wrۣ|YrT/)5֫Wך`}nj C0msذl6lA?ɑ$T%TiA*u,=%}'2GLUIF~F…[3V}6̣c` 4kf:ohƫGL*4<&/DnG]O=ڹ1UHb80nxG3u°E]h 4kZ2x^ݕ}( h w}HC|SBS-e+Vf60@݈t)[ alW 4LhZ-:dVLGXW0mrґPUz!De F:M2C4T;X4_akuQt՗ђB]apU|pPj+8r3Qr\ LS|$02ZRhipU|:0ͮqzE9c$S{^'Sb:l HҪ#btf GĪw*T $l4A1wض|9ty^,xj ΢ \w9$u ])'黸эSkn^ȏyj>X,OD# a*IM]y4iWcIÅi gDZ`=s{qoz@o PKt=D^1flot/jquery.flot.fillbetween.jsUT .US.USux Xmo,97v(]=/kq%Mri.iY^h33<3%i69lIKue5۪+:TнF诶ؕfh_.o?g-Mեy}3K;DTm40-awY*gOϚZr4ACUD[csbGZѽ\*]fn*ƾШ&ˡ8>\+ye_PZ\f㥨jDU kK0WmLH[&&WLJݔ.d >k2I0`Lw@ͳ&G,FtEsFW>;SbeiJͿ+q7+UU:#O@kgڨLY¹wqlߍ/Tj76Ei1W!mvFUYk~[?;R3ֹ"g$aSbWE+6HX"׺,J]s2QxXJp%*LijLC_cdn[Ř <ǧN:Nu6MHP ND^(D@VծH`\ }k㏃GyƘ9Цw޻}`b?HFh_Xן>kSNJ ~=\秓k]v[ߴ]0g;_ca"8!edc[G^*t|>>}2[Խd{DќL7P*nSA:PjFÝhb:=S|N K| S;u{\dF{ޢuϚ_PC?ZƍԅWkdkdq:',E6=>@cL\֞4ʏĻǏ~pf[q/IJ1\2Ry~w|G dX RɽV>%AD r(}ȁZVromoy6 ?KO/4?BYu¾İN}xju(1OF_w-UF0| CP\ڒK\wJ׻aEw=4%xV1VNW'ձ"ݞK[NY |??HA+@ VWRJ7P8h N)rT;t^hg u(c$;= '$ek0Cv\6 9M^:g2?5d.O rܓDϙqW"а${<։N  GL?Mgi]t+qZ 䤸iB#eq\g wgKg:n}vac#Jӓ>mAu&+kgh*FpY"X__`b?xdǗPK:@D9Bq #flot/jquery.flot.fillbetween.min.jsUT 2US2USux V]6}_VaJ8RJ[Mڷ8`m&aa U!!{_{5'LR9Y7`[rpƼsAJ ג5,~| |1xj.0^S7́cu"ktwkskA̝@g9b~ޒ<c:u+\bDٶn>/ cs)H{ ܹӝ'aH3cI҈lB"95SJʆr h=u|ba2SvcY%tpɌJ1 !rI91eC H4׽™@o #w!0t>h)tF7c R|ld wF V \f}N(z}yf@L,fKTdr9Kĺ܎:&[^!k ArX$=ɱovd 8ξu\4Π5x٘x%^<3E]0V}iHRX hF7 zo=ma?:3;n k)M&Nfh1vѱI?ݶUضyaxT" Ӕ*bMܺ)k:M)xRcI&${T Z%ՇM;9 ii[A7п 4iZݦ3Vm3ݤQF~FO%uYY]w&7-{ofnrжԲҠ"[5*5}){4rCu@}l-l¼Bx>1^ؾ'OQ//X_O?ȶ)Q2b2l"ǻ!u(gl +T'Pi5 Ok%lBB#Rn `t *"A6Ju€qyS3;<ƒ2M+HآcąʭXdp_$LGe EvբCJn+{n|Qy ЗC }#/ɡD98-Z!mc'n@8KaD'ꏢ l",#A#I3V-B5g6Q*avx29\ϊagH%~Bqstf#ƴ`B橈 ѻ8,zC:۶82>G( AhgG #$ SW C[#8Zcg|o.OxͪT>ԓc>=,tDэezDc< &Hl"ڮ~E9+`<~4XU"0$|R2%rDIC<49okpvd3`;nv;\)uk̀)HǮ¥!)d]g<# gpFk 6ruBYjR+N 5pI䣶85=IIؙ$"~ 1QBq,iN`VҖfTAr5.A][cت( !e(GpWfN^6B*~EQsn}}ZBY9uz&z̿葿;)?=]Lȇ&9n¹:(yc1xm܉22~#Y%qPDP |v+4Dn܇"%dru\=09\+U.q17!ؗyifDד\@1O}*uFs'S{ m4<Xrml5Ux70&F_5\M nesP0QݺH2d^nvne4mAatlN%X5>Lg#3jp0(jWLzݑNǀOߨ.ޟGh)BM;&pRj[gQ!oOsa cO>vX(ljB{i4vY^¤fBh s[ߎ:_{)VkOVPo9T)zynOM!>{oUՆNԼuo7|p}?5OT~řV~ϵ|IEl (Xz&N$E=i>Сώ&S`%60 TY!S%hRx.0l8Ͽ|auKmIL@Ҏ;-7ֺ%|p3dca X$C2k4g i5AgO#i^ZMheTZWh킫l iWw\,c9}ʅ!XDsEz8 Tw"y\.wⴊ XMT8ܵ?SVUmZ[jZQSOQxIԯ)ߺ< I7MibVųgUW/JMU?iF=uz)v7$ z& |3L@3ئ5%iۄ.8l:MTSm"TupTlSp^ĩZ=oTe:} <_(=@A#:fqppt!2m;x_aW'>"@NxהFn3=Jhwh\@C(ơY.-:7;%cE!.Wp804A:$|yoKnNM#'~ ӊ^-~E*^j*%<'1<<Ȣ~ִ꿛ڌLYk7x|KɩGekЬ3=w9ޏ0 -[A^9Sm~D@Y-W4) G) PKD@Ds9 M{ flot/jquery.flot.image.min.jsUT 2US2USux VKo6W(ĄV,-,HnoL[ʒJRXYCR/ڋypoFC\y'*S+Uy/^ۗK̈́  ??)/H/?.eɻb̻/x v^]TƼnDV n.}] rPDWVFLp&W-?҃Y\2L*"JRL]%BSPh\~ڐdLR>5Ni?T\-J^(ioB L4 929"$E wIư󈕍tʽW=,R hZSDX2 %^u5U950*sܡFL.~ [dRѽgy\J(bsVT]3 cp K4im嶖r9`s&],``q^"g 5?}|2!J1T)Rb x;Aٱ G8U vc0~/"Sg{:]amDNf)r3PoJ`pL7.%T=n`8&hLOGO` !Y X+='|;I3nmY'kfhĨD @68T:Jh='٭0xUa'*aXUċ&B7i!H0q uЃluﭝwg|:w:A%ribD^ ѓUU։6 Xj A$˱sN^, A݃ɕh0[Ga[1h6M1Tק6pOc49fæzC=ábbXXJg)U?MyHfM^W̎Nf m }LFO^yRemp h7J)+}6[ k6֏d_kEHyhVJԬmcpQp/]QZݳpFLܧ+ĹN2/z{k> zd+2qGaO}OPKt=Dd(vj[flot/jquery.flot.jsUT .US.USux [o{Fr-} /@ EJJl1LW;}=,%.D۹>Ҧ,fggB?k]e2+:g*K'.7jZ?L յ)q$:M u4<W?~t2^UY<&LVybJUύza{xc5M˪tY<JDqdKRjmtZ) #q_M ,M*J ,/jFZ-Yy}]Q"I)PL~1qMҼT(rVEnmHFX##تP&Essez*އJ SeY$ i q9fК*IgۻϾqSp- "*Ǹgr1OBg|e'I+-# \x~Gg|tx8|Vip,(/ʅ #ďӝ4F2t&^!2H~d8z{ -P.U>E:[poIGƳo=o[|&CWy}YYxIX7q i_qdvLV3<ҐRr"-ZxEW(k^@LޤH63"%^?:b3;'͖ c(FǏգ <6gJ}K"h4+\ .v>0vc}0SߞeeeVh=n69Ab?Ci \ mB;ONqeBMd?vi=vc;H wrC,r+9\ B׻?bw6D!4{٠XZ-sZ|A.߿8rL&Z/C+hDIG0տű[2ԿJs~1<&&;IܮPbYx:0輳N˫v 98 l >f"hjdOO񅞁*!+XDO>$t(wxB:u2yjYrqVd g ݧyΊxKgٗaFEz p}I{8 Ypr#/G!Du˨qC,Lh4C ~/C$3EDoo^P*RZTS̓k3OP{|ap)uQoM:,PkR-O5$ql 3ķ.Qԅe{P,T]ТibAbjPr@c 0)(At)Rj?#Jj>3(+%K*Ltl)%j8t(V5LZWD:j6B”3bbZi@k J"ŔNUuGB#IGُ7  BM6 dP C;XČ3ϑc'l]g΃;־؇U$\ i.rI} ѿ{:foTQwY$L\uQVJ;xzf/TU)[F 'u[VI!U!ad@+wuAӦM&PUW L1XD xVe5Iܾ`rؽn`I#=3y*m zQO;H"F42VԤZLI2Q0 =Z #W-V%0Lйeu ղR;'UjLs* bkBAY ~5qXuIfBx,SW#&_y4/ {#ϱ *kb͞}F.ѿzBotpW: ;a4OkO"fޝHMaA{fs~SJV_~m+8Yr/nd!wJsP)rLU3<,6oBBV YH_uP|=P%5ن0J!s{ݷ?GCmgFNc0`{{_^AoD1(ru9RŔalZM"1il 72Xq Sp:Myn(%ϕ)Nm|'_-L26/Y"7\pNCNC~`32t2<^ބ|]a {#GY0UR. Pq_H- nVYZ*Ll<|GB?mޓՀh#~E1v+Uhm&Wi/TKvQէ6,>[㱺oߌ):AK .4!H=6.}/EsCBolUi&{Z*lHsLfqzބa X#!nU9ƂdZ91AvUkaxK%1*9WWmb[K,DZ */[ $_(`3ӵUM:@)knZ|4hfZPդ6B wĴ5|zrFB" YL.W{LN""y?.;͐ߏ/)7HPMo$جc6jԐa t袽)l=o!.1.7Ru4I81U6tUZq eP.RBm.Ck ɣZ OH#E> [!J+NPSxh ~ MN<Ƌ2I7G|| `D)WCU0EAH()8]NJf ,llr$:k8PΨ$%hF$9"B8Q˰*-Y4r ٻoڰˁzDŽv!bӑ0?!#֌u/e–.frta#0+[F%U8I'sXs:hU?X .7`KN)*;)+'˞"3f6b zFݦ_D!#`we^Ƃ>“]8/t,H4Gm`-ӣ]EՔȻoAE`vrdZvbp'!-pH[.:2\ۢ-`/٨Pbq5Wo&^#z "U0_X˦cnnQKfz/sV,ns'.mjU+V"?;"o~ozܓ~:MSL:5R_S` ڎ(a9jgh7Q?ҿU}GbWpϦ5_f9w8[ftN='F9~t63/Mk+Lk2s-MeW茿By%g_ mcm[HUs.%#;WuͰ<֎?_k14\=+K85y69&:wx]IUa>8 eSzn컣5uZuop XxU!\=D?ouQՂy͹1 JFK[_2/,)9tvtѼ#VD-v]=NwI陁 ˁīzs``T 鐑궜+CpMMlrx06pm;Ќ2tA/]ؐkch͓$ny5R6 #/~H{Qi 逸g鏥67Zfh(L=cM%u_Q /w^) G;Nݎij-Civ*YJz24LAgQo"Hj[ T6&:ƿI7BDnt~C–v2 $T7b趁9D)CAhwFlN#CTضl*G oWkmWb6[ ֚Y9K+QgWJs""[ ƛ x1RL4pm?jq|Tgp1rq3F a =Ջ4pfş}鷮HlZИ t[}i!o T!}WWkY8kb^H~I+T&suLqZbŲPZilѼ^d{r僅9bE/K~?ɞ~4-IRc?{ 6A0p;<YrP6\݁k?K&l俢u8Ѧ y$MцbT1Es0Io:l DNnh#}{ưX\ ,K=iM]B0wzٛߕsJrE?_ȧ:YCiSx@=K{Q`q]ގekueidFfHN&Tݩ_h9Z:T:W?pP^dR;!긓Z}eM90\+? V6hܨ#c5"gv9V"vҦd͵17븸+nnVr *Bvd 1wˏ ⋖ m\:+^HZ󝚀VƕwU ;wBSi+`/ľ'/MTq_^ OI5hl/mwj8ᾟq;VԦ}K}uf7!ۜ+ziJғrU5o ւ_aL-೬&u^Fwd<{)M_oFon#7{)ɚ(ꑙllx؛LONlIml)3wUh4^ݔ5ٽϱnBUtMAGqiHR"5IA IA+LH.Nsv,oNgs4[>Xfc}G;v\w%vcM=0Tq%XʩAD-N?;r?3~6O9}_}vȮ7spԄab}WŗbNPYOsI -/7`pkyFD]zT~ C~!NxASl6#@Sz.1to6s(XsFv, L;-%,{dv$ } DL{[6ث)@Ɇ>I. W0b%9|N3_e$vژ^r.4 T8 a``Z^Ǔ?pɼH鮌Z\5Bj?a$GWdcD9*nm*-nӦ9A˾ U cIHb 2ˈnݰj5ޞf_,x`3 B{m'~NFb y-$Ql[Rjzŷyb^AFWXp&d=+\}f֪C ?$㍽na҈ry 9l D&'LS(tLQA7* ֝jB`SZ cvY /*P Z7XuhI[dx(AIzg²mNĠD/2I^B߽ ^^*[` `1M^Os^EСٮC|k+*@[u QxM^C 6zB-ʱF JDo_RQA.E=)HXFDʿ-{Hn:ZbLqTjW,D*&|}Ra&BkP՛ *Vf{oC[MȎ0㸣k#uu:+eo'C `]:/СBe:7E$;$ҩF}O!ys/{et^2k_f |$yWB:-nH=z)OE[SMMq1g.+ڠcVGqh+_A#; 'tuwE6أ 0nN@u3 ~Q/-v*;߰Rt2;H:~tü.quj{HCZ~iLoI 7R\՛Kb{w+RUDnyDSm,`*~:K˟J<(٧cV܊>`08 Dަ@LF ͖C8P?W|o@O~O=ENڬi''rÁ墸ҧkxGXڂզt.W$>JXQ RW٢]Ӫmth!ߒrH:R7RL=_[ 0~{K=O~nci@}mhO2p=$~~BUhn=,j[Ǿ?|㥒<Exk,/Zaݞ}1V!,GDȿg `w!NtdOV8I%9b{no?{*Zb'TeUkfk聍KUVLM[Lt╾vCzvfu[*Y_VZYWYx'N@_wɩӄѪԄ Mȸ[~耞NXR'Ȳ4Cn xZiV(jxkTQ8*WȪ,FWUmJf f{JC1f:ZQ;:Uu߹|[}~Y0C/Zެ r**w*T\n@Z,Havke-8Y5BuYڑ ُx+Y5꾠uNCv0cfa0wm"/GdyxAU,APRK%-.MnƬynbFLd|M*14%vy| YvAQL0id3EY;mbًم<*S:̚BF8#\~SB'V:ȲB,&:S⯜ G;SsC7!a:SAY'Igl# Ȩ^?3ͧ.ua('o"6aS5Gn7:[JKm R&3# k(/Nt0_vu'XjFa{} Pe2JYaV/UR~(DP8أf5٣$itk-@1X?uZ|׮FruB.;t137߭Fa͙#'3w6݅&X|'() o✙i 0mN|jiw9lnݦ؆lj\VmXbȬf@tSz W ) 8SqfZVy1U+yv%x6BX1 +5>ni%(^zJ56p;!yd"PY[CM+KFe~uힻmLϿY$9~w>GgpsfV%gnJwK@B)ytbܠ+EwmƄr 8hiVu]V冿ưYޙjx1M$0@[ڭ5kmfk8+mZ2тɮ=Rͪ _)lZBI5T&/>)Ӆf.4.4ú= 1uNO lzz"\[*0o:+sr!=$6OȲR"t7Y+خ0qt{_6!z4Mwn|Sͦd7;Ov<}Nv+gH#+2 A$EdXua 7Nn[~턯ظRa`]Zc % wmuڇ!@kC"'I7s> յ&ܞUmU! j n)015,Q'H.`(Pr+_iMNKX'8);u$\ysSf馪P3G{9>qͯ1q}Nm(~c'bNU䭇Ju䍱=)h(W:G[KsI2g0;dɏxuTGI+v4ẙypd_s8e}p)J.E4 q:p\{x,͙S\©CAZ EY6y@=@o<\&J?pg(+ya)Oy4^(-ɼ1(rp3^~şy7qy2aW?>x^(qQ?O_מ(+8y/dq"=D]+%s7Xx[ +B,^iT,ROxKkxȿlI7)(vj_StJAyK3d5"2p@:êY#Ys W%s^X5uWƇBD64''|-㾌,Ꮋm_)v%z 3+p/JW`z.Dy8H&zS,8v [q]DBv鯧6'cT~TϿ)oGYS˟<>җމ澃ōAqP"!K#tG|0?G(>D_e栾/KxW_b ^T4Z]kXHżStfq# !{$rsg8_n)]>ܭq4?Fvx^;X>v@1ȋ`GN]F_3y+YB1]r?ݠD}Sj @<,W656A!!qP譝1eC70z_vݾEW@o/ԷM{k8umS /ndiN( 0!\qtB":4 -{/#fJz;C}49I  zYvseҶS-ab-֍WR>KʢXrd>!K{g PNerV/l{=41mשP` (Z].T({3Z@c# 4]Sutq-MX ՆhQ<(RHuޑR|F~ťC.,f[K :Nwm](zaSJ "'Җ|6n>ZC߳w`: ۻm ŊEhL\Ox!ņ=Fx FTwa}B˵MOi Kjmc4f6y!V(3 ;pLD{%Vds(C@" U:F9lbE,Pj4l>=kPDe楐}$`wdF$]NpXת0t'c;C>uKD\>A [~P@{Sjd.0A.>3+'wq6B^%i [dYV=]l_f7ydZ6mK퇰-6yll'Z{cABP8O ̮żV} dԦoiZS#?՗;>A)S!Bۇ5a_t/G&+aUú롻z,[cXSYFqg-f?oCg2BDF7d"unUhSCY+2Ka(rtK/*؋]dD]nUg6Jα1?$fھh/.e;=(&o)Sd䓅b@&EDnɹ޳T-T&tO?=WŖcfc)]# rGY ),_iC_u]Y4“rJF4f KO ㉨su#%U+%yƛ#%Jb2!fWy 'fڸ=H|%c27uXB!p.Bf!;\: Lk36Dh8\3`rk^=!<FH/![M12Z_>ɠ5-nQ^]]X&՞m@3~Τb ,Qb644TLr\;meQsOl ꈱ%=9wk/+qNZ&q#C(Ǥ> Ij ٪"\#Hllγu+҆¥)EU{/6kx/n2V;sT}Ʋ9{n9 ye rr wھ E*"*Fv_FUV.n !]5|Ḵg !Ҫ@չX-I#+yjɸ&gJVq ޡBڻ"E潬^SpU^FH CkH:Ļ;C]r6S<Ѓ}; # Zx32 " +iay1j(} z|mbPڽRՂFYYT36-Z;{&$Qa>UF=`](Q˽ 0_aH |;mX. ȀoLq@Yx0y.܀Wno;ck…̥݋X@ř>xȺ C_&&0@:Џsq[ %àc yFHo2VXQWޡ,qr7z8G߉{MfQ}E(ZBVŚ"}( Q,ӌ4t"45*lܫ:ECe^ч@5M`T>bpݥm7uԡFmg-5x>L$|So UėWw9(ROdƕU,'q"X7ؗDUc#*9CYt7[uhڗ%Xud"^|A&Cˇ|l^8z47/~3Me4l0),6Y -,`k!\Km&mFLxL5{) VNqrhiΩ^F>vڮ8Jf0"%Kg74!nz^ $pM(W ̲|1 LUŦ)ʮj`p֭םQ?D5N F[UP.}k%6\:(1y._|n,RrG-S " :ǦL=<_PjF-8h`[6#MN|@9'hwe~)xuK7SFT QgI0J&40jMrIJ/Jb4mnΡk>&e=Yc¨kypjnWJ?g$hiu BggQ|O۫ӏ򆩕j[(4ddxjl2tM3hˎ F+POˑCO%/Cۋ+}m.nG'P@t{E5yIOVdrLe'pw? ㌒`<Ui@d0T;Ok&.Rsɉ^!N>ׁvqSLƟunj~牚s?]<8ۓJADj)]Z4ՐT9L+{̠NdIbt.ov'ʂVOh^Gk+>S0XbMx6ؐ /G S:x1m0QzKEFWqsƞPbIUh2rRfKd*uL5riIf "'z RNt,=gi$ħ.oWRҽz)L'0 W$:fwiEG16<\hdYMMvi1>.F&J2Go~=iX롣>)!IۍܼX}T YG8&i^߇!D(QxXQхL*^PDgu׾w&rGypI(~bۍnT zn*i#I7(!AղPO0dsM{=ps'm J=8Qu9=Myd6K^NU)qd&mECC7ذ[12s 5'ޮ!}!~-iv`kS`X೅ءF6u75hoI]1SFpF4{r&fZij?T`0?FfݪwEw~DI^}y0ow蝡GpA뒏}Qp/Bw*=bbK c"T7SlsәO۞""͚0bkF|N"qVQ{niUnyڟLpP} vnDq,UW'P~$tQh~S=3@! c꩎t3K,xAů %]LǶlW׏4]p#>nR7 F["aՒ^Z#r!e Kg-n#IAQ_[2U!l7"AyėV&or@%mV2Wk ] OO'qDdRs,$&+g5]tsmϒ1c H37M̨6IfN&?=YUcAsR |HM~O^*85e)y;QLT8jbmUV5~-nuQZZ0Cv]ngL$Qepcޫovm>"ci!/L{KMv&82aN}* :+%OAU@='A-va˪'[Ezl$ƹ~,˼{aK˛6le3&ޙl5hyɻk\G1mK2I ouMdNp&| /[mpAEn[ ixs{B#S ~m<g$W"*^‘MyuG%!4%cC6vȥѩ~^.F=}'{&uS;~/UQM]2nkE/zT< Byׂoipnt0R3:ӄገfM!b٧5A'pi6SMX,^"K̰-tv*lU[1#~lx?'}jGA9&LOREQ }8S3NъZ%],E])_$ct~aI1_Q1ճ (J0%˧_@]"gvm"w% 'n7 17-|ocnW2W2Cl1D M+hVa▨z)vH25j6^}ՆLe^yve̽0^Vij?::C ])~>h~p+_@P?F(0OlLnӁk ϺHK=4Vcc(?ٟfP_?6#˷6dݟ#Cm+iqe1h+=ѾKJ!!G냯t\㋨mjg$ ICj,HMU}.l"] S "U\*)6-)q[MNa"3>`UA #U]3O/'3h"Dl{1{S@cjlKc>PbDDt;ݡf,rE-J ?84)&;]6k]H#<֖̌ !eRMP wo $+sj:qy)TT)sq0Q69Y%ri4$>.2FXcm.gMD') ^B**>'b]i#8#T5UZ3U i BoA2q4usEǯ D\H´xM Dѿ}gmI}k#xIE.pcoYݲYX\Đl-ƽ.2X&'#4_|LDYQi~dɣdAUkր9T6wܣdbמ bQPcW|RQrjoG;zu]mdXLWi&Twvpƴ>e6PqD4@)Y\d$yլ ?IM~8"wp۫ݎNTm;ƯRAo5ύơzᾞ-,|EZh'#OR4trۙP.GcԿlvU@[vw<㡟st|~JQL[[ F7iZB$S#H Œ.}#2qwrR[4 ǖ4!JƢU*y*2OP]̭ 9qQ3P>5* NLx39TM,<06PE[-SqcR4ݤՁVRPbÑ@TY DYP/asBLD#~|ߞ@ \*CkBBDӝ}rlW}tZ,}Sc>U Ƴ?qz5B驱vAɽr:-i#{["{[ZO[C6S#qˈzd @߳65;-ѧ-'k}h9W#ZNezЧ-'7S>mYOwO[Oz=킖{E=tZb+E?ݒDVK SRo/Bz`Λ{Cnt4ԥn\|͟Ҏ(O XA ֲucHCp #}1rͺ@gOƊ~-'_2{'%&շ|*oZK@,di{uTZ|?' Cۼ%& ^N].7ޠYT.\|Ȓb 92Ee<Uv" *()Oĭ#[RԸr=L UCѐ!FCMKty$&>ׁ#wU:O8)zMgDٙ2`?TT6>&v}MSB |/K_Ͽ8KP6*j]ԑLMn E;& h] Gj@[\q0+ܷ;ޓNV-ƣ{Bt?t`a7!6-@'hiQi&j_.C- TyJ Ϳ%arSf!٦TcHhʟ6 @h =) 6ɦ,!hjWb~+d~PFBAnWEY!ٸҝJWehBvg~H""/w%l:osnuCdZCOs$ HCId\1#[IiuDpN-f)F68+EȰ-y)?'qTpXY lYSA&D}MS !:/6 h绍`U!sj>!@sHщ{ti^VNﴬ|0@v r_a/}cEΖ{L%a]UjeyqfC ?}z|34a`*$- h9ņwA;(QRVPd<-#-`Zv ֵ}V37#Py\z<}$ʂSuSP\fD)rNPqyË? i99W}TFPgq{tKϾ,0+` b{_ӳ\dywg}l{6f'حɺ@xߨquv oSرgvڞشsp3[YʒfyCwD] ͊rZFh*`6jݕ枾tLwL1?0d!Б ˭a|ƏNPPFpө9iҟlE"i9yZTj?HGp먻wލ(FUn2E)%I&ɮ2ܙQՊE8(ץ6l[с,g+WUQ_츩)49Adp> J%)@.7Y$6j I F>~$2nlx2}EVV+VsEBANq˝;JtERՐI?v:0r=#~):Ѵ &xr||l#+S:[C,1Z3g5NJω G :Juƨ L 8XpΛ~AtB1oHMغ RvHKyNLj(Ȳ#@g͗:6ff( &#]ۍi4_V6`sFqWM_J:՝ŦQL9oE"d-Cɕ A1_Uu'm4^2TYp\[> eH# 'V: ~;uߔ "&I. {~X*>ҝffE&y”s:8N$|[8ċeG} ̆ͩ ?èkA/jfVڥ{V\>l,73z,ՠq_JY0+NQ颐;>PbVч"eΛJu7 dž1{$g2&-M =1s E{7/q7ڔ/a{VduF YqHBQ< 6I;@Wfwɂȟ"LE*t?I!reFy,Y,9|f[RP;T _eWA~]e2 UJ+(}?ў#8kHgug&ϣ= so_fduBKY)G2.SKq![s,-eNQo0uaوG&_n)1b<: ҄Vgze Ϲ^3W<];NTq}w6>-鮜x 3!z aׅT ߹,1ś r1eh.ڞnϾ A٥5CSЏbFV!J)!?QBkX@2{fI٬3U,EyG8XbVT ʯmk]#Uζ#z ' O^Zʻ?f(>eެ>4M8]xr)rE5CD̻"XX,WȂ”ᓣ|0upl@+}Ȼ-x!flV/'&/q6E>O s_@eNT%ӍlN;42_& \g|#U_ϟZ!0 L?[*%ºd4LۢN$!7sD/=䌌i1|RtunFN۝wB'qO@/׹;ImYLkveft+w廳=z#R2u'|^a""`qFLh-B=t./niQf 4v<&CFIQ#[^Y^7دǓM-yCNZHUFm`UM!@j.9> fB=-/ؙgnE2GPֲ!wSCM+睪HIu(fǤ#hX-w]OjrVW$g~<-W=moblqܢ8LVIM:|=='#]T}6#ծK }S&Y^ܤSrx#>8yky\mm\; n邢se5].> C=Y!iE &'D>G-V}a3]Ht[G8}޼ݾypovŹym٦ξ-O:lKL*5sDŽ{pQi}N^! kLH!#]$T_y)* p@;!㽺'JaIgf᭸)᝙rF, >~ڎMvsԶ}<4Z|ɿu}9~͢ ?BvE} ].>;]ՁO&+bHj"pRDcw8 E0: GEe}=H>40-CK.FܲsW_ݡ'b ,`tCG~;} {<܇݋VnjuC}"oWlfew'j-}(8eުj8QHTW %yJhb1Ń2g^%̷*_łP[pX  Jo09Pp'  /Csgs !*AG:N(ΰ:73x˓dѫ[ukG I& 1ﬞɔh YNQڛȗWSAM0-Oǐ&iZaqG~z&霝&^"D"hy_ rWâQ_,sDz"MPxl&M>Ps]}67sn4FJ*ѧ XDFB+nUW*쁝1f5y:Fk>C&͎h*i:S+ԟ8y[v;cdrT<jN v@ps4V{XBDX$o7~E+vVJ OE14Y-/1Vc0aw2.PQ $e26W+Qp<83`S] 3nJ2V+ K\ D4~vS>b@ d?X2q@ܿ.N-5 yiJřj¸PAY%!͂ySq1<(s?^wp i0`mƲ Xh y4e40#Ӻà GI]%P퉈1fS=^l+Q3@^c: (QS/ew3 N 4R4uT28F+k4!16z4lK͗XUQh0Y`G1-@dFPvg{-DAޟ8_%ot)^OA.Hr)&CK es܁T= b1rWL ^Φp3Ho%$k!CU*}'q.-Jʤ0&^0۵Дq6 n)d!3c$vFb?1i9V7aIuhEfeG\y iXΊaOr:\$|v.@HK/y3^zv=^ xqV %Q]O1i%ze'V샣؟ҵfVɤq?|ܺ[3?Ob~72䖌-Q^@kE ?c*JyK߂>/9mACf82ٲ7*ۨOZ6Gk=m^YCy 7Z?6uC_!@EI&V";9 RS-?I"?Yw;&㖯wQX;N=eݹ܁tZ"IU -{XjH`AjPtv QhL$x9XXewԵżdmpdn0p#0IؑG$g(4:/JQ^Q͐[-?4+aA 2CTNNm'EZa&V ~K?3!ČrpW*&[ -c/e߲@D{ԅ M0s2s? t*2nӀ85j2 "ZR+DãԪ&R,&kI%ee$ܫc@O 32 v ^E7`vI>-tTyel؆$׍R9iJny n; kIm*ey*BZ-l+;ͦ?g|г IiTҤF3p+̽8n-b}3hzO(f!*gh\r$sH+ >x8Lu$Y05~0ƣ&VS,0%l0H9nd^{W+'baB/Cآr"wixXnGu*W*9Bc$|s7KWZ`&Z;a?!CI>yFZ#z'Z[CVSMt/Js?kT7uyÔ_E$Q2^]C.Of̽D ~2 g=XgK b,= 'C{fp9,$EmYT?rmȰwi^/>k`zL`\tbxNG441K?r^< HkJ" %hRP )ƐI10 F >(P|"UU~=Xuqh4N22o⣒qJgT̟)*eAn@BWlEvlw bjlv!uz88g~Ԓ{;(ٱeFli Xp` 5 [^eΨ-xPTH.*T[X\,Y]f)5ۊ|YTaYԘSVaR+fҁ)aL}&T饞^8rxh+/5=bެUu 0jU%F cq7JXӶUNP)R >A~B5ENI*tG63MtyzO׫"=[6P7^~p1yM ݶt{@rr< C{P_ `nӺp#KCaٞxޮerjkHdA _gKqջL!)]]>e‽{I;Q^Ub*QFf8NL@G يFj1 {m;' %v-ggX*nn 2%. "KKҚf& }ccSqbY@V%#ҥGfHGQG:Ώtq&d5H7w}s%}Ӧ≉WnqO;]#N~;"8;z׀3Cd` .](4v@GeޞU!BA@{cTa !F|au>X\ґ_=T?|m;Cض$})mId9ϔUssYEAE7F-#} bp|Z(U ܖ? : 4j G[>۷;8+֎0ֿn6TXcGRBFޒ5C_24(PLK8w:gkSQ}/g*.<]%nġ҈a&0hx@@3܋-َP7!8), dĮх*F+yJe*S-G(tٙzL 0|?` kF*HStgVdRҥ MRIȋ U~WŢݮeRzT#=v 9|%_|yx |sw$9Z[+W~pMkLʵý<Ƚý<}=m`s'vHݳaatQ/Gv#R=f>)[=,?òòr|7Xc> eϛy>ۓp(DrPc4y f}ӈV Rپ>>j>պ{MLF̚4B/5OEKzl)| nѻdm)aɖ7WuL `Lx!J^P{vgk]VU FMPr`#=J(VX>OZpgu" q;z}cSͫ#41Ψ{́FTWyXO'L7w0&>B4^ƋyvB<'!5(5l8>~WFmRbLyF)⏏)rq.sZ(mg1vÿ<Vdgߥs# R;w1B}-wIJCN<=`B|,efzI xUİ EkI: C537CE@0|sߐ#4hT,TgI4/ "Ё*SiLF"9l$]ٛ vɳ)C/:\}I_D5c|hZBz^8"?W&{NWzTW=y3nj-7>ʮw+ ΐ~@8L'Z̊Qxubazqn>,7yRг-̧-P9( xDi@|Pwۀ*Ṋ<{?aM܈P*j% -l~,fbI/Č^*eXa 85,͍F~_bmfH.HuW]Wv/("#r%NDf.Wuj4Wn?'y[d4@>}I^S^.TrtfnK7scܛ3Ţ"Z\:HBJxr#{%a&_,?oŐ5ۧ2!|2<-E,)U0$9B- P2a0CThvJϥp2A絴k|zNr.n r~;0t #foNO]ezaȱㆩJmƛMldUuoږhf -ᬁMԆso[6Ttv`b2DQx2\e54YM m_O9[sRY}9W6j[T@_|f܍BP^ gҴޏticG4GZSnz[Jhj*ַ6Ӎ!=̗j_s6Ⰽ|-ilr֎slt>=MY5fa(@(?`H+ 'ЛS.ԠorNrvSsdf +Kw/6r/T4TBcI6 NȓYærCU^H_zNyLaZ`2?+jKz ,.Jk6=ݞG]K_@lKU6B널Lsx`BmN]<5CkT%OC$4ρVt]P.94.VJܫ=N00{K(llI8 OE *J..z-<32efs-gD(\•pjtQ` tK39ĂҢ:`L.HN""߮!fo]딢E^r۩V\DvyS]D5zC%EnUiD|/%}&+Ĵe.)ӿ}3q0`r: M%/ 蛮L.\G\A-EU-5ENNnx7>`\TtiD.1.ya˔]~kj/X|xw*+KUa; ]J2b=MUjU{-UkUR:"VE{ WGo:sB΋m,w]h&D>=2C&-VZǛǯ©ѫ5tCvlaf %l(^ew|>1F3J gЕ-⺷ɖK*.5Cʵ3 gtQ"nj%Cp;@IOΦʃ[4<ሁ]kU$oFJ{L"\ ϭ WbEo cV)0:2&UܑYm6nӏ~7wSٴXNlyp}FOp$yKj5p8'-m?C-C]%NTbd[G*HbWvi~=Bh\2]0tXk4΀dY 6JÃ۟$R~lˏ]=Pјg^:@1`~f؜DO. }wtT!bD1wq ɜYYM"$q(~(w(QR_Ay:BRp7 N|Y = PPT~ 4~ڮ)gml.MqͿfheDSgqmD̽ ǩbVDG'^M`{ʭmrjbyR?)FHB?Ỗ}6m:*{{8<:{z*@Ő<R-xA GZ>$84[ RRtU8 /5(,"% jOLft-=Ta4"mߥ@e9 A8ҬwfRI'C[UW_EϜ =mmm$^4:gRz*"TҘ IWE_%T5f}1íj̅4&WYQ"| rl]m*QHc(q S+)zb-4&TU?P]Hc.$]:lW U{1jd4&WYQ"BQ(IC8KZBD˩Ŷ1(Z>SSxb*1=?ה}KY`@6j|޳_cZ]/]O?bk~Bۤf֮k&29 5`M*9{>+gȨq0VMxHRRG^6 ^ڿ?NubF--IO\zr:p;36 ϱ  C,'-1' )׉FA!@DKšmyNrǼp'}ypLOR.UX@hd!89Mv9C'OV<벖;x WJWg?d%5*y8*>;@g؇&|C #8GP Thbd yq,qA2-́n˜hN\Tm["TBdӸK'm'jy~x Ïbn0WdExI7HcBs9Gcfؕn; THD-Q? bIǹBp #Uڄ8&=%;U]/UGJx Ul2c4OuM 0|3JGÇqχ9ZBgA<|{$Q UP0> N ]\rbZΎaq@m1Dڗ!Y9txF{UctD(6W鑈Ev0ȕ)D!S(4)t\˙ƫR̔+>)` \HčWGy] խvPaDRURJ=.ӺKK}ETΜ&9G+dz밫 f hᲢSDnU"nپ\'4?> Nײs%JհӗbNQQLeH9";.iI*+M .d^!ۜP_eyE"]}K~JWm$$787Q ˇːml[+#aۼFQ Yl?-KgR%c+ILSM?X#BKl+WEt{OO}H1 [}F*Hc9>~*w6cA3x0 C7|wOt9Q,!, bZӹ,F(F> 8" TB0dt~Bw1^uL N:#\t5'f/z^ 9tm)ͳ)) G'm,Uަ`6LrlES$ڌk=B:*i$oLdyot5ut݁$KI =r* S+9]Dէ:2n(66 9YMG]ޝo&o \rZdfSV7|6y.P.KebCljY;LxI 0|4M&{@xݿŻ 6źȈΤA%AU"AC6-w( Ӈיmٻ)hd<'pÞ5\! Ż~gĆy=m+@M@n SzP]\/Q BF/@bfv}m2zx#5(HN @ox\ޙ F 3.Ȓ;4<c3,\ fM=z?f:|_mSJ~i z4Ƶi Ǒy0,^ļʞ珞Πj6ؤ89_N\77FDSHJ[ner:W҅Ua&]XKmuϸ̢Yp恗t[`Z'(m`ӕ"2:+P|Pn>TprV«vblnm.ڋ "މ8vmiRmlÑOm2)N'Ĵx>dph2_=[KM5' V;yy.-;FNGWv}Hor {=ҭi6ax5I*.+ lU.g.Z c*t_,q_0WT/g ; v:mA0^,<qHg\41zNmлIS"~Իj뫆CҸ>(9$TTI8C8%f*U<.)}U|맕8e1g\qS{Yԅ —s.?(Gu)5IrA .H찘k%_bEWЛk)- N%5Cs5y#GG{aK+u^v+ns)Z[BnRC6Byf`{lhtHh R)c304D:dըer _WI^2L! >s>aCB~v ulG^-)M?DFwۯg樜bᇚ2e?^O૤'bLHf3O X6ΠNz{_*!NOe6[UԝeIO)>8T֐8c"WeG|{Ub+<ڽ ES =&+9+kG FyoN7SXjdIa>oa&a5l+,kS] # erpYi:?kVUkJel: LcCCs}h%``-~3G|o++ M&Ey|Q^MǁI&;kaa5 g{TQ4ap6S4hO9bImS5D w|iceFΈftmctCF*HgxTT/ S?@fg9؅}p{|U`Ia۲#,>Zo"0$ƱC EPaSfT*}w;TEԹ?޴PKt=D:׍7flot/jquery.flot.navigate.jsUT .US.USux [[sHv~6E5IM&"MOymoULNbJd"#q{s(I)}o}@?GI.VQc1OR!}?"0 /H%p^'m.\X-·ß·>>EJE=gE쫔|xEDz`WsYD@ބI0~R̀7ƛyiE@Hc cG\4 *u+@=;;/*r&J=^K$yra,ۤJfaWd9{Ir!#Te>!>OD/ g(25/"6B MfF;FX4H*8zOX< I*98QXaJǢ"Vg_ 4lnˤ?CbJ&'aCCLObRvA{" LnT"gQT ?f;C! G(wB Ј0T4!EL" 1*Pb5f{.J̜Cjڞ1 Y;4㬛YD"AH]ʷIYΔgd$0l2b2] W+p[~޻9b4^164#AG4 p$N^ `%A/eq#Hja8t8$*0ME6Ѻb.$Uw6h0tѩćcbǂTitY|3l#cg`nYkЭ,^U]Uuev4IX>RVy%$+j@#=I3%%$wnI kN.}\׵'XEdh$Hk+ܠ[B/lV#WHͩ$ /v(u=B.$A]>,\Zi̕uy,v^53]LBMH6c{_v_.dTǝit(sd "M`cL5_3-}hʼn^~,"HU8V$eZsO*BJ} XfC!?mK"5*!pc+WBKeͨQ/*&7"4#bBWJxrq~?2K_Gl0FWмs9oJ..U&:Nggtn~54[0Q09UJV:5j`/(eOe|I↴wA*%3 <_be} `"IЏz`J po?~~曜j͋#5[Ҿ- eL7zJND%GM¹(K!*-T:z4lwwX'| YR6/M̱k . Ebb=|l_"+iLݝ7gl7 4ضSi

b?'qߑnbsU(vms?$ $am_߶wҝXq=SJu,DֽV›Z{l(v/3e6l;6Ǭ4Mg.2rEcSxpVRc82IW"AoZ_-(s?A-!@ ,soI2ڊ֔;'WǸf*t48APu%P#bN|䭶m7Cۆn1vm];Թu4"%(ijV0?0p׍`W%-1~Cj% |AFl,e&bp-od*?c^Ϙفr%K%(kL +%]֡t[MqMVt^yi{%m}(_8GG@c;t,V psᑺAhݭɺ +7Ιm3^6Ot@b2sb;#\BF}V> ~'H]$ ш;_?/>~y  llnOI^0+>Q:y:GRX\vq:`={Gvo>}@̓SWՄ[J߿&ɷ̆Xt:@F*^$MK,xykR.\ ׎ :>H*ViŇ!'v'E+( YKw 5Ҫ;ɔu|4 H$F iY`Ml~űf=Uk( E|?^>[]xw2/>U [hRN1K15kٔmQ4FN9>JpjLAӫd9x<~Bǂd-T3ؠ,$ ;!y =9;|Qo; TjMn&]Yf8g3H79/Q%R  ꂡrε>?Y{xHGw.-q/ PR Rʉ55P5/İfĤa\T_(D~1O뿱bf0 SIo;~>RMZJwd*F~G[!=Or^񸴥x*[$=$Cv,yj𛺪#p*O:b2upG½nmRVjJ;dh+ww⤂lLzǽ<ԪVJ^qg֩ڇ'{eUi e:Pe#1ͧ&&h!:rOK^~T C+ީ*BG}1G7QGtW+kG\eȭ]6Ѻ4'Lte Jj'k7^;xۃ'q+2}[i!u +NxRG;}mi7ٙ~#R[-XZDL!QS~f[iuh֥rס\ ͳ(xutqPyUwk;nK͜zIĺVP L{w.M;>-qv\?#VVsa}p,ggGrH [f0x?JzU:ܫ_DW4wwq=[Om/S4h{;±Sr}j3t*r}&T6] 5.IRBe$7@7a{e))b/̝/W#͑mf8ۻׁ߼/: )R9:]xszjcb1X`ͣ!9:$ |/IV=d d~]4mƑ Z+?2!j51mlG\ sOruv==骿AϙyH(Sj>h1-waoCӞţ~x{Vz'/ jVbHeu/T P}i:s\A=k&Nf*xCI<\g AQ^ L엩X,?d=0qGL `}վ&ψ9V1W&o4Ujʂ"Wpzȍ0ヘd=㘮1ʱdž(4Ŏwklw?wsWEX|ib ]>XMSep]^BQC+*Z\x˛p!stsS7PKM@Dľ  flot/jquery.flot.navigate.min.jsUT 3US3USux ko{~EYђӢi:.K$N0+r%ҦI,){gfK{wfv/:g?ģ2)jHN&Rk?pQUg}염ؔ"-'dxxז":{,+'*Y,U+"0;;̗YX Gm{({~qR4Hb6~2wRW!\:PP`| "߻C,/J߀ mFO]`s,uSM1=2Gۥ*Nj<84lNds R2UR1Rl ɶ/*=Ee WkENʅsǴ[tw8OIMg"'j>ҢӲ)s{SlQA{&Y8q^MeFIU,lVJq%܉m~ Bpuf݌o;S϶p5yrid(P4,![zk z57sK0ߩ2 )x/Tʱ*wx#)BX&nq">cNTOvh_L& jȇ|~z( kO pІRb`ʆڰ=;l.\(sKuf U&ĊN*Y~ey&m3Ҫg8bsg TG 6yy]/  Ǭ [2LDʣ TmxYmycN]ɛַ$24eu&9am8UsT(+¾;U& Ni{A7Eik85f (gc9J $^Q(l|b%DDP7r[`Sgh=7۞6i1~F{CV! ۭ U7nZ)S2KlV=O0*2K72 8\7УvP.cD#d:C;@~?^{,Hl̗)A'5!8PsHE͜v-Du]抢H7*IB`u_2OSit~}1dI*En›(E| ^tTeE{(OɲCzuPq JQ[!ZNVҟVOiK cͻmj=3v2=~Ԓ $4e|2;jd?Wx~"[HVBdIVRGk=;!{ jd7q Sٴ6y)gQKb ^r~)~M~AI$2( [e@Q] {NGtj9 }qI{a3ÚP.ž Rz#Pm w;jB H9?I"<|YS~Zo`N|H~SL)7T2SLsVc ]2C+ޒ\4謿ۥCx569sAi :LdxHՐrO^Hk!:tjS1ll"_C ub?e+n Lк 3ۊ*Sa%-SٹF+hnGQaP=1\YCB0YqdpE["z O{Xf;2EE1  pUfD]7)';jzQ̈́f'C`T1R8k,M*1!  JBI_W|g!HF\p&a0mg# i10Ӟz5Zgp7Шot!xݺFOŚ/dv*ZAO󯄽@Q* / .GA=D3^?  VQ.Uތo|C $CtT7HD MG9#IFVݔ@$U4&wS\tO#O [iL"GW:7)N7nC47m[uâC7_-7H}!>Qk!6-n5i13yO/::`˷8 ՒtQ:?tBH%H' _G)IKH%䈲}Qat5~5,ҟOte-?9]O}ٓH}rǨIq0H>zmnŲZ*ƚ*tH2b4JZ2<;6=bPKt=Db%x]flot/jquery.flot.pie.jsUT .US.USux ^ xEQUd)DÃ,#YJq-Jh8z.".kz,⣺*c"ҝR啂)"^n[y.UUOJ9LrUT D$FGhمH\fb@ B@y)/U1"nho$LDޔY): dٶםHS$K`3q+R2T3 |EDoor&&YZ*,-4b\ s Fy?R8Eq jy,3+e 4(='\]sCw`'b+[I\.(z*g',$dd x3a!g7%.wrR@In>Ai0!V4Av}ӈߙ''';ݞtR^cB9A .<(Ԃт7s%)`e@zP85 fiak$B8ԕXUV 8RƼj u+%5s?6ֈIN*L]|x%<*O0ޞ oy5F0`KZ! ן㋋7>]#1[^[`u"T;Ü|'d%cKe6V _\J?DP{3\KKjZF7!zvnZaprX|f,Bfh| BE.f I"a#B\3Ll3^Se i%ٰ|/879#~j5s$:❮1~4lmȬhwRF/iI˵m$u༽x0ip M}T9:z m|Wbh\Ǝ1P oY H=5s+|LPK H`[4cW3p0sT_K7vXhЙg/{(n2eA @?R.xG=/7}G5 &'v6[Kɿ:Uy?.ݭtL] %'@V  hQn#f9DsLSOڃOj~xnh !&u!/o1E >j@lФC %F  & .k$vwcc;v[n?FV\čARl>Jpkd/B9<03S@7cZ4>f(#d)#f$]@fH d@7G^MeA8/aʯ)EG%Qn`& !JHsBBxYݪ"t0.̀?Qӂ7cBKoU O,DG+UI9`w<OΛyP0䑾u x~o< vvk91λXIÞ0l;F` ȝQs@]!xe蛂cT]ϵR1*K֒n]]A> -b'vr^b9Tˋ<!pU8JZA`Z@PعGSyđXr=m7[K kwniSN7Nÿ|9uzC"^&i@#]{RjAvF,JV^B!T ޚf(iP+-州y\)/uȼ;3+JڦZ,f:~{Ɓ j3gɣH%X듩 >ݚjdmu=c+4B5j`M?U'0w .]gJ;S"'jFT )t{NQEr]6]8a`,N"pc\ K=8."VXO?xw|ϟO/ވwq|.>秳߿yb;c' 5rz9>CnwEEG [(-OBıwI. ݀{D(.Q5$5cjc n1pЋI(Sɥ1Gl*F1e59p&P,A Q&t=+4ueAvl5K6zGi̳P$rꪋvBZEh)󟖺x4jTV ϫ*)IلLY?[pYyhAx &nJ3X@XD! Hb6T{LO-ftBep=F&B^JG)!}bAgOHKH RWMXM1NxD# +l$pT8csqA$S? "~&wF'U{R0R5 XD)B^.'eEv<ЖЀm'K㐗OP=Sv'EQoaM62 Gې|V2Ġ'֚:ۜK{rZ>gE n$ L[t3wub1EEJ#,fr#j:jJY/O׷,Xz>Ko-kdcfIō]DRʸ]("B\gq{'͛| 2V"XqM%.IadxCfRԳQ nAlՏk!n{F"o0n|W/wA>Yx:M`y25n-rme[?!E_F8OI]JFo2`DA 7Li_V pwtvr(QX3S:KmFٖlW ?s6uP¨'=Ulj`4P 7]GN\UFg136iji֌&b&$eҥ xGW7kvoƬMs3ײECrRlW=׏Ykn Us 즵vTߌ&W˦lm Yjz-đfWBVh_P-r\hbE߰=}-FlNش0Ouҵ_ZHI}c,& 6nWok]*7Bm{qd1f3'6=W,k+=1eȽk=}+~սyLQGv<[laAqrЁ ROĞ)Vߛhͷ\a4 a :[零;xE̊T۪w8IԓPzԧt`ٓ #dI;`HMױ]y]oL'GF2F~e 3LRse?貁 >~z;-l'Yؑ 4] VQr:6pǤvD_$>;;[B%UFx.vD'{~ t=Y6MF* Quk6rI8,ae 5?fs( nm{S=E;=;@v&߁iT§ \=JL8*mxP.}>}jN+_äqΡnmp=)Z#xmUpK"o9(<ղL,83IbbllgʲMQ{3Agfb XͧtLQAP=NySS-զdn3A[guj,kKDcO77 c`RĖ3'z;!:pZG*6M}s>BuU2aZ3c-{Y{^lӶkc57B4,7z "WI/`eJ;_R+\ܘȥPF缣&271eQKsx2#C}o™4;'kn{7=¶jEK6gB>/Vs+Ywc5.d> & mG v̀BgO[̓)kLMސfbeY.dvEܶe[Pmbt=o;)ƠDچk;ҲwlHH%XWBFY_/nGՑuQVei8ߣ'b*AbsxV\C\`!? k͢fu[--e]ٸmP.b!Se"y5\g>\e1n<`4+ )t7Qho@JdzNR-ҝ3<*ޡ3Լ% OlfM`ѕQˤ!iXCX[)sz-/J^PGiHN>X@~@5N0\ [C0t]7tPKU@D"X /flot/jquery.flot.pie.min.jsUT 3US3USux Zms6_94)rV}$]&$1II/ RkE"bX< p{-,y,N2JV8fLїmD~㌾d?OMȜ[c؛<|(L 7y!h.B,Fd!Q/?BGT M2/~㯯}L<_7 ܟN|84q,`&0 ıSJfH-.""(TXzcq1ӹ(`$2 kj `mRg>kJܯmu3ZS*Yhioy$:nNjXтX '/DdnhIJ$~vsaoDUT֫:d2GW:6#J 3ϼaf*K(Y |wHcX3Ic6FNaZ&AmL2h ˭4y۪߯RKfF 9[][UKXY ,~{ގ::/-X3oz-M ѡD\=[:m859:2 aX ɏL&,ex4TS2%0UZ"AmReZq9eySq=6.P(Fz'MͰk*׾mG0ވ΢sqbQ,a:8dFF=Ϋ&6T ߘ`Baɍgs Fo5 r>[}qH!H8 }WMKZnLRaC5e@0*ϼ8vDg&\M YD !W$ @#<82P|E Eb%) Z1la9^KsLib%TJ:CD)tiǃ4dRR;KR(세qm9 p]82"S5}: YE?#uf>P"0~`^~%!$J` -@r; V A-'gTLڎ 0nakM}`NQu9^^Dnqwb(`cv>M2ZboM[Ki!T)"w,&gG3-ӸݷBG v}qHtʻ Y29VN!1#,6A#=Q#>Dږjp!h8i(Yf$Z^5K)ehh%"Ko ;FcEYX)&}Kvb/:,tKv""B1B@Kh1e:O jr[.2Y y>Ed4uvt>UN6ƛR}cٵ Tx|jh4ۘaWBaFwc㇎1כ1Oʲ$)4sy^ze-8 لb(zcEz \(-$Ǧ"Y3DaԴf^g9۳.TMp7qMQ^o(tGU.ޅPz`DףVv>q'2LBrِu+i$h5'Þx y>1dUK?% "HXU]!qxWG%y@F:Sgݗ4ےF+җ/5򃫣RcN>`FmY,'|nQ @PQ[)֢}rOH{OHr' RS2SO6ROy28;>w`pVZ|BO3~|^YKp+Vf;j&BjBL)KV"/ =m1 ps]z9@NoOR1?{ N %Y5]蔟-K [Gnzޅ5+N^M kZAeY$St; M=X5HߒҌH>W*Ӧ:(\ݦ!񈣀RM33 hwCڳQԻ{ il[yHQkۏ߹*y7=ȳ"g4dXd|Oک;#_S 9OK=6E431IUh|̲DV{W7iz(_]ɉ3j~z*] `eNu vpڇY45M9%˻%ZvR\U߫شNOI' zz;u (>7ȋNDN<+8t7u}j_9Nri8|2N*TnN맆&>-4)E1ax47i)/1? (YMk_h'At"O_lcvAI;dR r,t7z;׻zyŷ}Wx=uNCHGxQN\\G3W,6 AoI LR71aK#g+"ZhS4k &!41|%ED҈ sN*6Եp` 7ԙgM:/ NxƵX̕^ۛ6c<KL$ʖ݄'s Hd+ W☔04⸁ ,ҕi\32k83A8yW}N27cPkƎLln8k[ipƂpr._+/- Du.FbȨz(&~bEX\uS2]n2l:%eajH[.",ԇvRuXV MvQ45F5H/BH~?mTaO" $O@~/faxQ.=d>+ψcŷ!e!V]:> O#oB = KÓkb>FǷ#_]G(Q4 u(pw{R>aC=.⻏.vhm8*E=lx1uŇ۷%(FFl7]/D)~p9a|όOleE!}oD7uCAs=N^?CmCH\?͓a?[V??R1>2Icw692nۉ|`b#nYۺ ?Iv##fֺ3Gs:C-ze4?PK]@DaQ( flot/jquery.flot.resize.min.jsUT "3US"3USux VM6 ƂLiN Aڴ)6H4ݍ!%B zpwq63rQJGJn0Ѯ4`YtceE}2z]VF F//oo_EB{ѭ\ h>>=et=z%O <`=*GL>i!ءCm ɡY-crbBuaM cU÷! C':?/h_`T>\G0m2z/+?2isC0V)AQ*ykq#8_T>>igo.L_GAn mqj⇒ YPya$61fզj EYuWJv$(UK=h|V y\ _Vg@_ULqGUAPKt=DY_U3flot/jquery.flot.selection.jsUT .US.USux [ms6 Xfl_{wc{47ͥv2QĚ"8߳ Xbw/.GX"M΄Q (وLm"BB}26\Å'ūo?2YW"3* oP%FDT&/_|/b; vcm4Yn(Ӝx^Nnoޓ^q,0JߡޓP:L1eihavQ2RW1EɛW[BY:*6ރ罩u*[0Z&"B'@E`HXoyFa oђK%10 uTd)&E@ yĚXLޘ BSN0ߪLη$JJ*3jZn%^L3Xdg2Q9QF9 V{e=_ Y,{pEƊo.jYQ^;&J]~;˰KB@|Ŝ2.=0,Lw ]) ZNƱ2$gJ VW#N*2i,K2[4bmpJ a˭ɚZ]/<`JDH8\ރoR!ri~u4 (p2L[2R(g[f?F+ak<)Ph=Amv;LfdɖӲ %)@WllSإf$fnEb((d&5C}C#n]*`2G`‡Y@Q@% #[<嫗;"I!$e Hl BR95 RM2VyX )Ab:z(YK V_3_X?P$~" [c=|?Q举+q!f+i%gN,5 '[[΁dWXl%"kxX @[y+wZ"FPӺo.=}P"4)T2LO:xT%$k`=RuVhm uSD!0\ 뭀.-.04Y{jemqc5z @|_ئϫk׿hU-Uʤ-6R,=phFJ`u(Y6u vZԈJ'!:0΃/b:18aъ*7ȰM7VXkNqXdʍ?:!zI)@_hkxZk5JU sϛ7O |!|N'y/w'AWh`@k4Cj]b^U{O8?ь䷈ZB~@,Uw\m(o,mhwH`_*J ? r@H\b#!:ʇlxkKUXCF<DR7xwYT)U+Btq!E[ %.?TmCфN^Ҕ(s iS! }t&Z܎hF컶öAފw!^:ĽNaՂ .*EuVP 96WMzCn^߰[xXA'&0Vkޣq2U7t薰8g7 Q ӄ[8t&kprş[wt8{tLb )n6eGM0!8.j9nJM96EK5dS9a޷Mʍ4}FZRyz_6>_j>cE t ,a8xG* ȈfvɋV.NϦ#zasThll@' M8MWDh,K*ӛfu>A Pg[NSKUqXO/|=.=:B=g'HԠ.S{"e7"(cxq_v^s K 3QW ȉ:CAhJ 2exë*ʬn 3\Hn}-,Qm_|d^ۅQyGJ~e}Qxĸsk`yxЯ'i/.S_fVꨉVF!SE"=-3Y 4);#&נn)C/]ncK;U G?L]s;͢1$="vشPpGW9c. &ll&zp8PZ]҉IOR!}|yķt3-Ln:@rҔyRw0 %{VY- #Kq[ʓk;LrDb~rcwbmKO Yqs zG&#kT@Z5ڿB r}hVs H ћ=;~~` v4qZYO7g!%m|gQ;i><o5Pl1lX[Uol2fỉ=B3\RvǏ޿sۺxPR9?PT$c$t7Gj)go1j8'eU"EWأISbD{UXڀ#*\i -K<$7Ոq,gwgF fW:ؕ]vNk/oӺ}ދw=Pnetפwlb>M7΍Φ?:>a޹_tdhΊ:wu6%.FT ё>Mkc];&*)<.?tCcCŜ S,vhzQa_+z1BPj~.}q,&ҦtDw>OGG3]]u*}Wi*a|GU^ >1A;60,6;K&'/M٧ȧIF#O R߰"?Y<a]وHX3yhLg)S, 흵gyzQʘAp8Rjdq6ްZَZ.8}H9W7T|=,X6 <]I6&V^U5tOj(އͩyϷ4^*lDKv8'Dfe%4z1  |Ldz wLۥ٩<8 iON.>oU;,"xNA5@$~MaQQmZSMأ*Pʩ}RYy$㉱a8^*DtCvAtln-H?w7-Cճ{S:W$M^+|zS+%X8dXxC^`u<һGM%`e5t(L-q V6Jrw4\l\{"(hHjRUUNgԑS+UPDžt,ScyJTuѮˆ/* Wj_?A;/)4( z +ӫRX1rkLZb4ʂơa!݂Zmg;I%ĉ0NA9) G %rsX… / r7QaRȴMtY+2Fނh'{B BМDCJ&O Nӹub (2gscɎLmHV9(I5K?DZJB ;ǘ6?uGI!bS-2 ZB˴!9PW`>Uڔ~v9f%BnR<-D ĸ03»fCO)ӥ2V\2ur{K*t Tz){|[K]-B" ݔ `عG5 ^=+_v5&ۂ,ʥu_GfÓ%4'Ⱦ;Cp wEO[ ]O|%5k &y.4{*TUk<Ʌ1b@zVTNna$(SN/LBujK]I\B<ЋE[Ү5W6z֍. q=#7zXc\Uى91 ̈́2Z̈́ |W!,T,z e3xbi<9Y!<iܨ\X3Xnf.N]HyNSﻫS#5P9?$7Ck(Jet }4ՅhոS}13LMojdZK}XuؼyWJV'Qf%~8Cm L-pGa; SN&7=4߰+(mPg*,`-:΃ת݌hrno0sݸ sY_~\BaзO d{aQl56j [^Qo!g7XpwW'a79m0訉&ztSЭ1{y~Mv _"2+i;V@˾7)wshA^՝/F 6 a{DGp:hAnיoRsΆhM$pߏ1Ͻ'[G@g8զ=k-`6bD0Pjg {|}Uh|Eb_N.X@A! Ge(U?:",5A"v%Q9_^@]M׺#ߵFV)#|JG:l6FDцش2ҡP4p;Az&-o*t#DB`l+r |ͧ\{>dh_PÿH Ɲ#nfb=g(*-.gcdp}qb;7bwy_-/3`4B*3 M\}A xeNF=3ABwn3<;m v!Kv[cI,3&i{|wy&dg-2#Fq;;ɟ#NGeՅ\V? @\rt4H8';2- w#1?<12,zv{ϳeܗ{kݻ=x] "*?vlQl.޳_dWm齮354q2:$|~PKo@DCƚ flot/jquery.flot.stack.min.jsUT B3USB3USux V]o8}p$Ү8ˬ:V;oQ\`mZ }A ž{|xW,A<+l2,h`wED+ Lߢ͟oݥ I鯓t l2q%$a#Md*!_B֬nmk+f'AA\˂UYֶ1PFozmK+VIf,sH^ V􍁢iL?QQFNq@D:x1FG[ *Lֆ~ 1eJGTmFdl) tuz툲u4~kÇ\S=wjAggt5ׅ8u55 ;#e2QfiNg$ pXd9.q{r>D j5_G⪹ ,TDwy}+w#%*_HJРl18Iʰ"ct1Zp2o)͈ou9}v:PQ:v ZϵO\je)W2|%jZ54~GynZx_}mT<=އ]kԗddڎKyWA2 dd;lMw}t,Aǘm;zZLED)?Jw~l8Ϫe`>Me2ŝͿݷnڠ |PKt=DWN flot/jquery.flot.symbol.jsUT .US.USux Vmk0[(NS; ʠmXAX#&;IvI~1F/w=zN9\h(r8h i@):גZL\XHZ3>B0UyDliy:˖/ %M?s W- z8F/E()av+13z/ֵc3n bĝ*qJG}B_(Qlr`xb&P;vss=77hBuGv{}Q}g+Gx1 6/ {W[@?>;;g4X^nV #akJ^ovU]o'n+"; G`^3δi60'z~aQ,A $ϪiMС6cisLp . sI)PKz@D(flot/jquery.flot.symbol.min.jsUT X3USX3USux TAo0WxQIqKT]ަ\pWbS?!(I٩{{~ϟ}g;AErr񬙮Zi"h5%QHk:|SE&3K0e^}F b2E9G+VjNV"xJrL&Lu)hx*5Zp iJH1F6oʌkx-!abdO*Y*J T xp«6^Ahb-T.$ldq V فZN8sh&H"aBGx͇%nQSqrʳb} =kxkI;gĎ&t32q6kBA)(Tgm~1N|D3ەfJ4ΐhQB yیv!m|aJ|zEé{PKt=D-)flot/jquery.flot.threshold.jsUT .US.USux Xmo6kr(/0Y h ˇ A>2mHbHKNR`X&w=wGs>B+!a4صf҅+X0 x0/gW?˧w>B.H4|\pRR?nqh%W~ml  .C{_-c"ߩ`7nmuDȔ dȑ¬Coy9q1^¾ Ck8=ƃ˚q|^ms2m)x 2bM7s6O V7 w)_ZjL`h`؟ a2M1dEs[hL4 fܟ𢢖=-1u2" :3mGi0p҆=9K Aq>]e7o!~f7mzK18rUZ,|eZ[me+kW.kmK3#Yڥ7^ e|&hO¯\/PK@DgW0!flot/jquery.flot.threshold.min.jsUT h3USh3USux UKO0+ BQ*H.TT*71mֶl/$!zy|͌=>95k͕r ~-OL.ۻ1 ^CϿ/PkՆ wLȘ6gխ d/~؊u1CX?Q jwԆiLR\3"KĶ(&}\pazKjW"2$֠{Vg!2dP qT )4{Re9ĬLdq ӑ HkrB=h rPbI3*#Jڄ'bϛDH/.~bÖܭR_vg1)Yv16\0Գ@)TI]1'pģS>#$ꎯj-VQ)SO(~ À"}r'(8DEQElExʬ2'e$,+xǯ=I\:0Pjk8 MD!_ YSelG&ZlZ ]!zBy@;GnԼ׋ݸw'lMMh.εUlP;2#~~@djWh>iY\3cn_fwڑ7٭m.#;wRfxi{X@q8am`z8ƅu>r ?6hO lKtK:Ɨ0S#maHdymP(M|J~`c3B[ 8@ ?Q٫qG /L S#sX LZU&jk~ 3o̼|?a?gE)G[OJk \>F|7#khCbKfDs9cjLiXYrmKM|PQ) (0:f 88}0||:X5isY a9ZY'#mAZe nF+rrb? gDRlp돮lQvn#-l$9w Q_;pEZйM.(rN9+:ߐ;:^ X`~XZ>E:EJ⢣]Pϟu 6+TEelvp` #1{[>/xgqWnCy ^M'^?kw  $fzTsy?]GV_E-Vpd;CD3 Ueq̈́8?hU|Γ e% 9pBG* tk;aVS&vsØR%[%HQvf%m`)ł  J@gH1,\PiЮlk;O'л] f-nTABƒUrf47^78ߤdONX&j)c{djhK/x `|,F=3]$)d19jT+빓21( 1 &5(={LOE$sU\}XwKAS`ϛbE/}h )+:Jx*7s85!O<@RBjM G)*3pUr(2'.f] BEogǾu`T` <[@Z/zD)G^V%Xkq2W4`jOumտdnM NU%:,A`D7ΒJ`X[wR7X@< 0ɘqfMf^Mf6ӘIwlX8yUJa9R>epe?ds?)B{ݒKe(HK3P_X ӛ4{ԇ2Ht ՔՉ;|{ϝ)*k;$fl(6"g/^HOY3BM';Z#D8i:08 Z+vw*g'aVaʼh˫1[~o"(D)ZPg?" j =mUKN9("jfܥj_y%><$L>vLa u/QoF+Zœ˧q7a1=u-5*o I1,E'ׄ,;Us cni ,=ٛM2l`Unm2פOBUz;aȅHIT[Jr Wx`eJ98@ 1Pڰw _a %a 9WSHZOO^Fll]Xs ̲|,.OVSxVMrA#p)*.5xr;^]!=Կꡯ-#65'kd`1Ox{|DJ{+ c7%lF݄Cz/SmG%dR  a`-ND0=j}B1L) $S묋T&p(mpΘ}EE6ɵ|OlR +peo%֬R1Q PMۢHi~ccʅC?L''r^$Py#j_i޺de ycsydb 3zzvYGu]%@A6E1ZEXt2Ab1u4t˜kg84۩nlOZPkŶb.U.ki\sۙcí1D vnˀR6yRC\+[v;S/+lK}Աj4;VrvPr,,Ȓ$NYe:'#t?u=4]F9$!4]d鷰Md&Z|>ڟNW_F>;°,2o&702C^)J1VP@ѯgӄVNdi w&?veJ= 1M[:ޡ_SAqJ8$1B  X9"@菺E2W'"onH$I˯/J :rꮷ95Q(+@-miO{?$s$%}5mlfmЗ+ } (~gm[ntJ|*| 9^fw8xhRc[}]#Y&%ъG&Por:sUOv~BS=4a> JTE4006m" #t1mM smn8njOyf;o7AEf&^.~x]P̃wx𳃺\WNTz`oK;7{ MI<shô&SV e$`b s^ҲYsR^7>Y-*-kw V*e{Mr^EIdN+I*SS'5gYKb,W8{ sH^{}{+x& ^ b z~2 n8 5jCB9lme0B%N>˞ }F96F$Kڶ "@ip@``_ZݠkhMlI%4ܸK%*YʾViO-kei˼i>"aa^I+8#9TA5Ř5Ѓ:$[n*|5p JCxXz\UU",I-T2'?io95ۺ+E:bGK١ac3/f2>Q&H!f S$Zl %Ii KQQa\fmBQ,I  h:R}XFBe*ȲFyqbdUY,I]U౓Y}S_ƳY>bȈw ]S7҇äq-4HJt KG-\#CIMɃ"[F#m. L0J0#_r|>9IE ď8 vp>8$lm7(Lbw_g?l =2pszaƲ±54 |z*,()nv8xwϴ.` v(L<˜:Z9S+^O PrV P,m7EOA8P&JQ3V<ܯ<+A3l?T kBjMN'D]Gpa>!RS͚YxuYv_#RW<'J޾vI) au3  _eAy 4`h L@>܁ 5Zء=vhՉ7 @$F}F+-;CU 'hV =9t4a5]-oYĔ=Mqj6 Mlz"RQwNXX%p%3W GHZ%UTHTҢ5P3F+|F쟓Rv=j oMϰ :NpmKSNTBMl5m>bǤ=ڏF] w*;oe!$R23 C4L/%zw(6D\q/Kq!k?ζ5|bӗkϧ& aCUހԦPv|0Dh$iܦ`uްN>׌ܦ D~Y}SsɁa,:Oxr> |}=dMV2ݴիwO{݁:"_gY~WI:m'vi -;ԣ3Su\%0 EĔwfQipT?~y? ?slI.t7|Bo ٺx<<6\8M&OfZAOMR9[8.b _ |Qw_T8፜/|2]H.ʌ׹,/3&멨X*˺GZV(W"c bERu2e5Ak1`+DӰt3xO;;,:Uj WD (h(S4by.3K,fWj}u VD VK"6[2.f[Z 'prƭޞ<[.W?0#x K& Rё*ܤ7v>&7h`ɯ =3yg>/Y g^_Wy-ڭQ.f7CK2S>kPS2Wr.|5 k @@9o3#g  OG_P;fa\^ ȇJEU/*F7oI;xpdDjƷ[@+POU$-+f$ Y@/@,TMgyU]-{$)J PR\\ɸLpʆۭ^#263^SdoDaWerp=HnlPmO\TxMܙD :Ç)HTŪRW8^KZN8y}E`!#%/i- 2>U~Jv9bqtxttqjg}?1b* X/QMҩH/i~z)$E\_{gZ3|+ ~?;cW-)ƞQp lu!AauމO|BXGz|x~ѿ}q?x~;;=3:`/,J o/PMn"kK'T/pwh\Vvq~Uhq0pVR]ǝ[q;(n{ZnI, 9H( 7S=3NzU̧_""FV_ \q"J \g?@q.+D ^ؘc"vu:,9:D&#WdLC1f)bn~n ~'ycX„g!bF+JGsI%f uVt.%;27[ߙ&94 ց ԷKZ<sD!`wO*Νe`'RfLr1,80陜i[ f锘L%(\t l{\܀Kcsq{}n;/omDf#z}n{jӅ3:4Qw1p$=VHJ\i :8,[7Ib</;cA5Mw@ClCa6ECvb ~amԿ0.33^4g]R flSDfdT.DhIxI[ O>!ɄUo)1&F~F7NY(ֱC)]p"ǹZY;FC:[e#ˤ__}w8bԼ6&Xl9Jt٩pa&{iPa_#ɑԚ^D^}kS،6YQYOR*dWZD^k8/΄@ PIѻKlh'$n0 6c0CRGQ[;Nj-u fwIjlhYh&Ho Z?h} )mmV8#?7Ǚް7IM{(k .!@i1i'mtko7/1gg?? Oom\<>$?03'BSBC" 3f-@$ȳŭm{@aⲧX'Εbj!BrgC#- iŪ YZh- '2CeNC$IRBWDW}S]zZA3PY6uv-q q6};HIΦER \`37Gk76bv(=G^Ƽ~V^kFD( G'OK&fz tQ`*,y5Ga҂S|i5$;`[܊[#VWVsPj7$5WY?A'CKӏYSYl묍Qn #s,4h΁^Z8{DYdFaӃlm^9ہePPq=I*jv?EC%ȼfn0Dw2X#2 BBϯcL>1J0m3)4Ωn^4JlnW>cA%󯚌FW#=WvJ{Kw(zM;9It]Rg\8fB̑,3i"g4FWe*HJ 81x5fjw hA 1[Ckjs҃qw5]EsT>*P⍛]7׶3 i Aڐ!6wE DϹd+̲R(f&"R=Tؾ] [WČ46 c9}PΎ]2+.w2r:c&;-|GR}.N(B= Jpαbe6P(P~)%*:Xf\"aC!/4Xhp/4156CtYxQӫ=D[iKX؝8m50im*)<$EX RhiV๣5IAs^,QFpd)BʌS pLX'jlU|#1FG\َƝL=lV-x6MF!LBDu`s$(~0b++S5 y>0]ΧrQTbX.ua_\WF4^R(Ͽ<5AgW^f_1E$fzi g>2<kjAx7 {IQ!=A4B^Ssc&R2cBoVѴ!6"%Vsg^D 5cbq:>d!轋am\(yz |'-W';lmڙd@$A9T:[+{Ռ1VJTἏ+B!m&ҊR.5_ts$l߲lp(;.Y2iJW3ʽέy'3Xjo(FQYC:q"cxQK^1 H(ۣjЕ#,Gck}qt*a:(DU\PǢ9Y.mg уg??ɶC513Ask't5n{`#6n^ğK$aH%>&hᑝVyz/-'ţBZSG6L궰$WCAt;o8gD+x6vK#hM)8n6;,0ghs VԹ)Ǧ7McjSb$C.FEE]p-],7_pV7_Fx>ORd94.,%3UI dܸS6323t9##`UR;8u|Hi P5p1^/]jAu$8I@ 9'-ūD) wª̥`^4{u J9: "^Ѳ,nIuuuW^1H]#lL4ViӸOQ7Oڸ'eu:pOK"Iÿyzj-orBFŨ|W<)E~f +}%{;;ӾzIijzgJ>>n~Td0[bVLf7TM`rEw+1+&6AV3Bܩ.הvdGy%򆜟UFԖ>YaCO CԔgmdyA?1Η:42٢4&t1[bW]~Vi먴"ws_tYK!u7ݰ5ĬKݡvR/Zeq\{uju'_}üpA9Ʈ HP;]bNJ!59"Cx5Ho6զ`mBRxg2cuH{?Tl-Kw/o0»M7cud-nc/ b0U}f`L $JzN[Jr$#,wۼ<w&5/^ +;{]n!i XwO{,y uIS m\Y07K`ǹǗnq&vwz 9*lR$c:|wڻJ=9o31ڵ{u-ne5ZR|6>9rNz$Nն_\3}$/G ./yQ~}2^O|`_D ()Rl[V"5w)"_6!٢ ,{"[E _Kd)^tonaMo bޛ{ Bx8t*zh 1E'ͺIjΎ6Zzc:-5XNw$v/$HDHr1bs̃O4_{eG }_c5+&Q&QAOZ,5 éDIu>ZHvPS2. {mtZ1u^r眜atɣ~cR'QMxϱ :9pr75Ttm|JUxm8i=-pªzwGp'Y<JTبr%TWT SE5fcTB\q|f4H,8;w/bmy Zoc9Joϸ;鿼J0O{Õqba1مꟽ !m4,D;~vKs=bf#Pbi)޻pv9QElI݂I 4vxV5#ny>'9_ ϩF9sA!cgun[%Bt^&jHnyZ}LzSшV6^hxX^AB"+N #҇ţ#y@[25mKݓအ=8_'90D4gwÖpYpf0@jBޢyO.~ټ3w@_4^#Yx25+ :rBN$k OmQW3?G,.@ @-K()m.|19(. 6SQш"YSC'ĎXwΗ"\GtDf {Df aTw?-wM s%bې,%`!G J(=xm(!Q ":!U#D7pdQyG*q`8Zrj& Eכ5uBƸ-W 4r0/)OȫcDr&M _p+Vfs ͇" %w,ixQ4ضSdp,xQna-Qжe &̸~o./nzjqZFNsB Expu]>IBS-l2}Q&T G\X~WGO{X'.'p.J8->x:m'-LLjjK j[%"u#=|Kl)a.ĢW vYuO~as}ܲ>DŪh([""<1 LYIQ]L!b4<03AJ),/ޢB ,B`$Qyk^Tbm`(ؤ*uI\|%%.`HC%1ӂ P<=a6%(';on?x̓;Ώ),?@FL`Oղf Vua.iDKf&yp^X(v TJ\ ?v!k+l.i >131Iʉ'g՜!Z:B$FsyK; ":)yQd HLw_ہ!:?LOj-׿d[53REIq]E!3REqΣa_IW15ပEzlSQ _9WNf4hL_NnDr1 ryLJH geqZe?yJWN=k̲>^UB|-~GNE7 ޸khV;fxi$<Qy!Ei镼:+&SkȀSBlf$l;ԝ3 y#~62N75K!^7C`9NKz`/x.ltwYE" X}V-'lV)QEe~|!z(s-63乵"@۩8 |f-aoEA܈3;Do55-Tǀ?&*.}~th6k&Ό e``Rn!&3 r ̑0R.{M9ʜ,#zw.3?сR34 ݅GpU5רAcxaA΅pYu)h &PIcutZ SC["~ʢ;5|bOYKҪ}s%zT! 8苎T.zﵵR=*asDg*^Z@;?`r.izUYN[#?I)pK!}*1V 'sz1北 $Һv1/bcSIS)TǢ;ԑ!mP6z"kjRX!,6!;k!x\ 'Q\$-/8?IzճK3mA5IO_9f-ۥX@br@l3a4#(fzYN*{uyw5P X7NDŮhl2ǝY!ys̷oGLI4_#W9EIh"Hfaȟ^^ExVD)v9|7OYy$*C<* 1O_Y@}Y'^?K_'nːsۭ;- 9D7iS| 6 5'!xZb#PZ͝FsQ@\snnV/Aӱc2-dU50t`J\M(V)TNK}D,M 2rMA:/hCk ɥItMk˟l#KҎ- "Q@^تA!t#y(t#%WhRA5T!VUӘ<&vNxU/#NMZ?|y9d;v,j_ w. ohLşP);> ᰤ&@)5vy]]Fo66ZUkM/eHلS{l5&b_r)ε}& "hdsHǧu͸##CJ"[V),O.ټ:֪?k2— ԥkgѶB`ýb3P'0O[$M ^{+n{yB5Wʱ9K@fRC=v2|թRd5#8hd6b1'g-ߌT4׻ZiQ;dCSCϥLPJ-ZrJyPFҵkâԲ&![v1:oפ#7o!ozB/ z2;6X$'j"&W o4M(R!4¦9t2;+ K#⓹gw­ЂC%1S(_N dWt#ۚV3*tP'nELA'gX w]zb2"%ŝ7 pVbe&\#h/-D#- VSϫ-&hh\ס+݈{Z&^Sd!x9L,d3o⾬mL7$^4Q(-v(׆Ҫ pR"HiXZڍP8%1b^)y ZwqLBXhk06Y#66²*3WdRA"\VTxI8R;p'1bK%=ne\ . Ԗ j׮) ⚒7K UnZ]]_|Y kЂ1ĎNZhW2ݎMP":Q^K`M',"=eqGv7 [jr?efO9-6ÿFc H_L)YBcumHlta],,:Z"iӰ=7,>S8Ҕns7fI9}c2|xSͳyq{w3]x31 NwxwvDf^Э0c17 $>%|vR\tG)ݾaIlO yݔH9:}X]q[}(BKC7Z%c_pVv" M=Hf;}oem^,|]Ep߮-y>-qwgyn7(Y0N+Q+^s>O߼~JE5ԕ!^e:sGx|mBGdHA"?@BiEK1Bi9ۨ5n?/a2]m_֣By1)~c9'T 웟Tx51]2DlPr]e-n C 5Ԃk,c~j|cI .XGQ ] %:vyW<Ъm^N ZD,$  E>,4e([A95 JjB2#)v;ڋ_v̅ZWCT>B=,?bF&\d5J(-R';M,L& K 5DȞl;sRetz6+K`?@^ܔ0P 5Ht?*(66lD^r Z,J= ]e/jg,ѣJ bAjkrrZ3S! &a`ivJNp6=t#i|&? ODPS2OEiR4O: 'ߔS*PɧO%B%O; uې¸A"NQ ->nN֥edJǡP3;i\Ƽl-Y,e旋:a0Қ?iDI6eV6iyrpl18F(B<8%iD /k?#4!N1 ^> ?.KQeh B L4*N&1N#ָ +OpNY_ ·?`r/odMcۓˀɸH/O=i#>0_&r}t>-f &}u_XM_'*)|a5}pl7g.= <+!1]`Ԅ˩a!SHX5[bW5hۀ]Y5#_ ~wx&~.jƇ72'9b6/GGnE R *(Śv= iYɡ yG1#m7+~]C Z`:Tr8 bvf;#y/wPcS!Cia z~m99xwd,GFGoR!Mzur 4x/1 7Sʚf%WIƮ晲&Q? S;ح!?}c# F'AmwBOPz1pjeg98VRpJ%Ӊ}mq9ǁ[jAm+jΠ',<1?&>mTתcUPTsI5Vs*[Flkn{-m&)o"@F˖3k!gGlvm&Q O/Ǯռm*4V)5ـ';lxuQ/+ꢣDV&_sO!-P&p7 S6 -Mؗ| %b@ky9"\j&)6?~|~\&B8$ ݍ5L81pQdK *3;6 uꍩc4840OJ)=enN*>:bw3lVoD˿OͥOG6a%JF{, [O8F^jZ'/L#B ([ٔPKv PÇ_>ѷ p1`SE36}(8mt@yOσ:CYwθF@ԏ]&3%| n+^7~8C!J'tv-'g@{%R R 8RWL #KrlwӻtN̚y6!-AGNf>x)ZBgPB;(P9w`_> b`w7O:E_xHN}r\ϢDQ|w!c}~`[sI`[ETYhMDs}4@SXM7)4H/;kU*>ts,{N`@e)'P޾SL4Թp&+$qD/IT[<"3݊ݠF9q4/&=VI.ihիxϾƓ_=>>/=z-=S,$w5[ ȕ'$dH|o{z~#~o8Xb L#iy/%.^j*%N";@G8^indb ؠ 96*E@ A Y"(_VPj2x"s|ݲqxm''(W_KUOO]m^P@sLW*|j'U>ddJLjPriw섎k~Qi0#!B`tt6ޕ.K$/isJFZ4R݅U{qcZ˅:P(SNsJpǾ|R '~d]EP#5 y,QC ' reDuBa {TVoO!eCѳp"(n?0[v`N"K*-CxUh\YZ̕)&մPo[XMq9\Y5[Sj~mk5OPܒb ;blOՂ Xm9"F΀Y5Cʗvd%0DceNбlT pF U ׊w A,C KMn~|- >u =aU #G{F&`1UJ] e ۅ\F'ID[`a@hANX\^;%5DSIۡp3l(kXE5FL\2&DAp_OGuhqU X7 ڤ醽^#U.%̣'h~:@/=] Z\Onh9 "qdFO׉UT ,rޯ喅sMOH)[9Nr+g@S? }w'}3Xyi>UGXrV ;[Gpod2XUiD'Pv?!xc |1U>%eBkbR,BiI,?yu)h[!,q? Ê[ң.S~1|-d\v35vO׋=HeR0(m(,bG57gsz͞ V NtJ[YbYlIE/b\f 4mֻ >vEHeu.REB0ԤE[%$cNZQ>XqK^FI-ڦjҙwy$]{#P>`2y8J'OEݫb`WCk0f D \@_2tW )1a{DsƴȜzkHp\䖎ATEwGz*D唻 1xHO'A;ir\rSSx@].-O qV"h'ZT#!B!H #la:ЗxJy~{ܜ}Jg `P }uGmԂ9@pҗ L 7@pnFctG'WS?aIt' zg/yS>hpl+Шxwm3= 6_1ET#<[S٫v:ܿ Z>>9fƢO:Fd7b>Bip})lRpvWt[hes;R4ɉ招Mt=`?XmC3ThBh )q]ѤofzB7(&K˸J) {aMO_q@kD\s]q-%/%␜ S㼔ηtkZ]nmrhdncqC&}^1Z{uY9PP%@mE`-<{|1 n@ZRޛJ\YGe:am3]aǨ==Yj1Pi= hTp[g%Tan1X,;1WHYKtRcW\J*9T}EtH?W{:T}UbJ W1_)t% C IL f\ևΦsv0U>iiiY] 9QAҶ4aGՎ.7lrJ̚5yԂ,yvO3Ɖ1nQ#))~5j9#UOh8AQ(r^-^V nd|#xR-Z,d̈CTƒl 0Xin=nHH<(Rr{q=5:3 wE3rZz-\T$`xBw$%ߘ_'n@(dN(?ف׏qdǑ%UpHsbJjCn~ah$_asV4<j~f+q'Gtn<[\ Ϗv@N(>p, d.{)dchW=xמ; >%.yob==pkPpçrAӤKvdn8i!XM0:6-*Izmxh]wwYUQfWQ_3.ХċVA}ϢR=}JBxxN.FM/yDkf&!-?cXOVC6eI<C$g6^.F'ɴj_R ^Pkwe ($Жtz'¾˺%uq;N_b;45s >ohJ ŵPP"R=&fnğ$lj19"ɃJb^:=cP2@X۸kc/:I&讳e!ƽ&D\ ܥ_GRk8K0G,wEHאlDM'~?ts\8Ȇh`gۃ(p >gu9 "G쐊yU#f9"q Iv\5B FNjN&4$B.%V<z n rq6ϫnMm!I"\qZȷݾp 6]@l>E3k1Ua4y`FN!>T}ޮ]|C~ NF{5x>\v7N(rШSu1D :EŢs@/ً_vZdo74NOVraȚ+뿽YumrPG@4y[BU^`9!IZ)^LLmGVci+{??I#L'ӯ Q AɒQ JS4lV׋ 48Cм(-똱bS`gv$h5ֶZfǫ|֕dȺ{%`H>傳vvsy]" TDLCYHE }yK q"-D¢u;YJ5b#/{Bg PJU}[矄Zs])@(sCz})a4 NHdYN&)F|Dn?sC}7Hn62n?-6;1^]ۏ簘o C_bVԸlmW0p L'&7;ÖYbg"lF7u.n R6)ZōR1F_x^3d2)5Y ړ5c|!ߵJP\<[\x(yrMSw \ƿ%iԯ&rK䕼`T Ɖضńڭt[~mj6U Qrkć0Dn"4/lKovSP O󈯟y`*W?~0u3H/p).0ӲرlfbŸJ6U)BG0=Y':: V5`)-]4_X[z ɳH( I=TCO-`<ҲR! C7WVx) ɱ_Rw|ġzl|%*4t[nn5v$X=Y#WζU:?&fv9[t%-Qr@Q;l?j.D}XwL}I..@:ߪhIVZ5JnCK _Ir8IA]y]7SU>X,!c˼'vDs5 8%m M4|&)z0ḣ+M50z|KL-Ϊ*,dCi>&[:%VDT̷^0tjAzr,U`B1^T璞p ],uq:9ԎInnr/w›=2C_V=.8!݀왚;iSF+2HETuڙS"*0`xD2po'U|wW޻GzKQ&XwFuRk%X-vbnEIj 2C HL<əح7M~/Rk2̣_: 'Ohp9^r~s1ZE׾ѵtkӢmኅLʔ\abYl}guj#G?UMmD' {5>!y&gxR?Ȋ؂%U@:*;Yܐr*1ŶBĶi'jʕlo|'Cx]t8W:?!}w㸜/K`lbA,1g=u[*j9a#w]sBm9ORnes\~>s#HRC? ѳ9d83 l^ 9\U%[}ujNiUgH'gݡTw<< {.b5ԯt]e ϴJ:hUxkUF1{ROxms⴩b5>sC9\-V d9B/٧/(ဝԷ'#k+ )(Ȍz0qZk 8u>ϋϸm4Z7?ى2)06NIJ`S81x0gX ;*/ y-ۢ2G^UiՊB2WaSQΟqQ>.xUR%d\y'ώP\7VC򄵌'l=kIch@0!AgE2e~I=J3@vh $Fɻ-b8n2+|BERߤ 5[B٧2\o\"rZjҦƇ1h)Ou5 >ͥCcrȅt'.ӔTH=sTL T,65g) B s vWCV|@H!|^|FQnL{}٫<"GyVsdUN{Pm[Gb*fKa K u9ĵ88?R5â"\G /$KL[8WsqY_~+RJ8`GVdJٖb}Zq!ƣvvl6[ਪzq#K`Gwm̓QkD򓇳.螐9|?5H+ NݻG(OɿЦ'6?Yِ {<3ç pL"K8{@p>Y0Dth,)'$C/|E읡D HRl XxgwryIi*PGu| 8(.'V 78/7dQ1BtQ~cRg%̐ڵ#ȩbܙiB 6 (|g 0'Mw,@{3ZEL%BO#]WwӮ/q/76ƫOm#lL;:V-IHj1('[F 7JD٩Dfk:Vn[Hq@$S庈 {AϦHt%:]l#T( u-?yx\,Q XȀc-|IZRZ7V@4&:%+ܚh Gp QPF`:qFHmImI&Xz ge:yE@̞37K;7-;2k= &Ӭ?i.$7gqtLv2cSVN+Էӑ)R 2!uMDhXbmϋ*~Z,7grsrmB71s m@(ӎ*>d &Aw $]۽m__xg,'b7[_놢g8 fwe'e7ߛrՐŁRʝ*PLo%$mΨ|Ϡlv #M^m~Cۢ>af$I+C-[-{" SzϑdhZ/a= 3P6RsҋH()j;Mq4}AULkhs֢fKhMw/eJ*꒨ p$:DhV/f3(|aZÕ*~} /0,{+Y0 8:bPcRd>Rc`̟ Yhn=o`CN2JjU/P }CŁ|+B51s}N`S@9tK !.$5^HF{-t!6Kj]кj> '~Ss^kOy.4|-IZpC_̀g=%wg{֖Q|6,!;O(Κ[D;$085ep0 07tr0lнBbؔppq Z($oMx: .43Kݴn7]t+ ӲCt[iPϙMF{sy($)d sO[fA9:dBE_6nDhu&ZRKgo]]5t9,.x f/G9~E{"E+0K)z3┠AmP\PǒF['U$>G1u48r]B-_ʹk΀h+$7fqEӭ[\W!;,ZZT3~)'Ayom9ęb/8AL1)Gf$NWA|m(V,rHe"jUT_&'k2i;fǁZfN ,-jO^o3P%q|Qi cRdЫAM.n nqB4t*h=|m]mBNbe$OV1V%!I%K72lFHn *GI$h2=.V i#ni<2s<2E엖2у$KS#u8)2gm'*WC ,έ(fv;6NNmjG]uji.R:%agKCRNiHS{V[p^[}7j 1#}p{dJ<ú .×^5p XwZ0'UkId ޝs!c\˩ye7PVrtaPUgmR~h,IPaSͼ-h¸lkP)ý{k옱7l?NHܪkvBdH֠ P [ƕ3 I]St2/P"0D,k;`DU5 ߵ/XO ڦdxHnBi] ӵ I<"Nʔ&rǮv)hquAY IMN-ڂ'ʊPoCj_-+w}.f# XT1{d$ ߅Õ&i\Uܜ9mq)-$='Γi6tư 2-!=Ÿ&X}8LLBEl;ߔD'?^.ZxppѲ@oKO>钷;N PMTT˓Qż)1%hnꬱ? _yT$ۏz,U:bLThѠR?w}!+9FalOxdꜪhA+X93;^7)¸8lR:U$ kmQaNIoEx:z;J˵Lt!6uU?`yыN|]r[*9&ռOM.0īo3ķTԃwoRpb۱ r 歜/T,^B?P&-l_r۫_!t1aKt&%|UBpCwN=ixeB9;Gw%V oHу|j4(l0g OgQ.1iIgVFbsQDN蜸AdE`QUcHNQ?,@QIm2LhZ* FxE*9Um$Spc[o/O#ت%RYg Cl4"}(aQ@)w^ QL aJ聓HEOb>U 2Du4'k6upCz΅}Y #?8``qp0?8v_S%؏wB/`,qV`ë_-1: *%l/WV9Foœg)<Ȓ}YQw$w)Bϑ6o2}ZۛP`+@CvƜ{;r3 I?9v3 n<hޯ_\ý>.}Aor[Ľ>k.8ꧥ@>6ktg~Q7}W~" C3Pb:|#Z 3)0B- Ӎ (tQ?|z J5A!@\ 򁞠\!q?yg7VotB4nW_{}8&>|k#@ oh>s۫j<*~u,+DBWѾЙqs}@{{nb"EE>E}8|87-Te1Ld_}ՖFת6_ 81|i-ڸ7hyFP )͸^R>l[i7mRd\nѭ s &|ǷO< \ y+U{0'/6iV`ݬKe4o W})`C~oӃw[x콆+cY(8 $'N}6:S5ӳ$~ݗϺd\K נK37O^=ot]2{tKuڿo\.]{ύ:%u N  TE$%dgd!=3baހDשԊ[tF"|ɨ.Md|r&.ᰬ)]iLGpEk$7QsEPw-+BziV$B-/73-Rs o]/# *[8&^ChvǓK8QM z.S Pm~J~@?bFu SNI{z?GP D)mt^ۏ U.Se\OҡX &wJu\Ǩ oW9?}2sy=̿`a:4jǔыautC>Oz]AwSpc3p?kf Y?hjиT72Hv,J ے%}#RmrD*lPj^8ZФ0%Is".RvZ؞OQh'oTq)/GJ];&AFR`"z in{pܿR>cmTtf k7]s\i^l!ز[~mH&leaɅ>$svGfPfC9)NH ^Mjd1|,>9/Bv7(\YT4Xxy]hkV#Zd;=EJP k^9Zh oZ)yLȤ\\3g Qۨgw9׷Hy nݶh7v覕&e&ܒߖ"r斄u"f#SpL%MWhćbHb0CXã2j$pBdQ99Tsߓ@ Q)#(;0RdGC LIyB"f΁~# Q2%ή~@Y(9aG|< 2toD*w_uZNn4p'FO+]Yz6~L6Wn\Үz ΃.1 60@V{]@uoxhn k&7=_d4EE-*j|bWJkؑAI5LE+ݝ!e/℞.*D#y NKq\(5(\Շx+}ת3da4;(+ ϔPEɓ5%jye mc-YPרeFYQA[߻`{hV}.w /G@^sSɷs˘?5R]7`'pOCm0_wM^2M!m.֓4Fk?ZKw_Cj**Gxr`H"?8hʚ\/Nz6h]/%l(}rRnn^ToŇZ")igYZz+΁a}Zd5K9 K&GqorZG FTyII@Ch!E/)c!oJl\ wQp`?}uv:L[wSyxgؾ|yHfmjp C ?ߔѭq/|08@饚~߿t7{eVS.>WϿO.7_g-mVx߶H}(ߗ 7z&7k[:yy GKeFZ 3i9 g M:94crcks;ݑ{a;Sp_r AvqtÙǰeys54U|uhGCoN;G2l^GFcNʮwJ4;p歼ᝯtB4ۉUt$9t!$$Yn< 퇇;$,~kז6BLCAFS`uv(`ZD/¶ d4yq״'wTM&#nDiP42Z5ۀuZ֩A=t\bЎc.e_b#RD{ϔ?l"n@ӵal3ھXYSZ3fbe),k„UG!p=QNk88[ ם5;P"<\+]RLpm &N4`㿑Ջ.;jW=Ltn j5B#-r:eb րJ,xk`!I0Q7gvBy7Fґ{[FF߿c$Qy57h(@ḚϪy.`d &뱁2⨇^#(:Ν0W41D^K-.=ݔEL-.f(ٻ%Wny?` tRu\U,qb?tK@hrּZeБ]?prAńE8fb6WDd)o`pmޜa8JӼP?6RE-[gC[E#Y΀SI`@-pBYlj~gżRH#EU#5 ˄{=T1itS׀)Hb*y)_'z.D;fZ/䣠  hoȂGRĴ0"Hi!cSҔM_c,~ }@HI!&UY50'5޿,s!*\sNI(QeG•|ƈ?b?Jyx1^g7[FEG-א&e/DL+ _9ot-BH0 (%% k6Q<)Lv`J%ع; }@seP#ÍImw C{乜M* jM O[a|9/uج}N.nv.c`Iu ;jWH$~wazu4?gBeYϳdjt~+J3ΏKE i7[nu_8~~N8 $q2&].h)tqIfqw,ϒ4iުzHn@ l$@ Y"*bz1>NGU+ sb/BEc %nHAf y>n3-[=bBH G58x%j'|$Ҳ"7\4ƶ Uݴ#KXQzsͼĠS8K)P* `Uč9'=vQUA>_% V-Yg…2d%BM8|YYVOOK9+¾5_/ܟ΋'coj"@GN;@=L{ExA|ьQo &h?Vn pfD-h]7XjOj8]e@H;J@E[k-t`yvuޥy$F^]s K_:"= @EukL*Tnll%hg82)drh)k.5 p94x'ҟ8B#Yږ:>N >9y7 '8QԤ+gN8/f8'KN@bѤ%N]D6,2Вv ;E.4pvW(o !F-%kӟL.K@Py1oոH})F(n^N?U&{z6AκPe/ %Ѻ'o onD#}_oy&7r%}C4-Ҟ~_8u؟FK>!Av*v7 O`m9Ա.EH( }tn~kq'B/ =sJf)|^WShF(Kb{O~A?|,?9:Ik$59|y:zXGS +|aC_1_q p(a/.G' z׍00 v[/zɮHYS+0"!jDFUPEdOJQ: otJ^Bv7&MNzXgTN@$yŐ-i84[_Hi|ꑆ{6? $'<O1R+\НuXnIZhmBdNPasZk֊El+]NZs5{x`,)QnHPn^rJBX,yQ HnAH3?³).Dp ZC( 2bW)gپ`Hk.'Beȸx ]KCx@Y ؏0kx}0^T'z̹ϙZuNqUC͐bGuy@ӰS(ƐU836LRL gb QmwX[dƩG/|~T]1԰Cqj5ű] AbZNn8=xQ r' |)v3Hy_m')}BRP[-\ꝣj>C:te{xP?Hl}אԗֵCz ma%vƮQ[]K>\cN:p᷌\+mGbݻW~27jVOGw"]%ea'z ӑ`Tf #)2^'b'7˩Q׸JOŔ6  7ii''!Ntع.,A|e -Xik1Ao~/OI42\@G-W%&s jsGٵmRudH9gC(B'nP0+t} @'N1R# e3&G͙}yNbs70=9 ;)ZxqxqFJʽG4ӓTɬ'/KςKzũۗ/PkjPq˅*G#!n5"-Ėzڡ3Ys:B8i{ $qrTƤPL0G=Mu|sL KC1k5>Jq M? Y#MZA hxѱ6Ƿ{g߱8J7*1[ !<z j=qp$ډ.(%a:ZXۧ8NI!`K3j]:UޤiY}NB4OLIKRtiҼԝ%y பDKJ % (ZlUJ]:Vc8b"pSˇ2[+>1Y UH)w y}4N;|CO҅4.|73)Y/aj,@L}ȴ];bIAfvp-TewK> NX-ntGr2k끞_ߥp!I( 7֖4%aꡳBɦ}-;챾$K"5ӷNXڽm, DaU(!jQ+/|왅n#al㌆WӸvq2A7ԋa#SlC 5}xhHPmU9&EaiR;+3 agI2ߊE-kh5o[pN|;GD8AF$BZ7 %i;Mh4s-"tLz a9Exr+[LHZgO.y'7fn5V3έںiٶa%PUvΊ!AE 8^Ls! a$Mx]d\B&۬EH0y$7YYsIctVMP&ZQ|X;*{=9=nndYuqE:ͨ. L[",R<>.ر@Ow-W/^B,s0$+~:9m,\|_ác|ʝGN:N'Q>{x-]}kEn@a,GVZBR3I$(M+DLd.%>hqGQy/{W0g5 kIe Lr}n3<<#OR"O ":.%A:SEBK!GT8!n/?v[_Cjrdoӄ,~xCv&NSQJ m;Ad?}bPlqFKA<ВaQ*_׿>Z\#{rjW<Ѭ06e؊>TEzh"zΉӆDyc%Y:ڰw+~4B*V,dIbpvМWD@,57ZMOO{))۾ S TLSi-َ֮8^d 0C驪b:eȃ&B)p[)lN*X7൫E.g~]-OjcR!|1q^zρnp1zF0Y0;O0,d#=fgpnaڒ%T8 ^Ƴp8'90gY[K:>/Ώ"YR ʦMьg b.' !=7zIW cD- DKPյIT)ɔؽl%y1j9d9l 2*m`Hѳɼ Igg.yTep'LnI #B,X@z6`П Ys&5H󯪣!pKz){`Qbhぴ_0c ͻW4W´xl||u8LN=8v5r Q׊Z/gi|J/uyVߵs{aiEcEq\PyP)(m^RNҽK b7Z,84n7bo$ q2 p|Q VooCCJu7#C^N4(2nžҐh="u6uJa<]tljRikWwSr7V9̡nK@e)+EzcNN_aO|nmW2ˬS[yTqkc&PH_w/v{|cCީIAhu^(3=-Hϒr#0DR(\WJRk3%#83R,Z /ԀE3q:`HLs@fa8t}~Zn*;mrwZە^voln{pb5KnavZ}/,L]O~uK`Bo w^Um$ۺ2{JȟZJ1FNq~sÃnqїQ,6&Vݵ"|*9AjX?$tSlM%6~k5;cRdٌKj) B82 !iA:टby$so\4d{3Բ8b߮b!(Z0b1Qb!Cl#:~_9byOx.UDN:B:OGrP݁tλxqy{c,68bdߖ;h"hoo`X*56w>/w+43[L|=l`HF5=SK$Xݻ_lsw˭f9S;%OJ9eW?s`7tGƍȫVǩrYѠjgo3@鞟b 譃5>FYD$Z:C !SgM[N$x&#!e6$?ST7>&OaPU+3:gGɣ8P1@qruZ.R>KPI;?>Cٔ":. Aɵaw nIi^vL`Ԫ$.A<4>jDZ`Je.( >u*Ϟ#]ۻv9|ON:YFn5+n@ ~Dj% P;}NCL3f:[Ԧ6hd?zP#R /*!anH.CObD.&&ЃS] Y02Z [,X쎟p2u+ll ;ETvvTx- ,õ\I]DT9N-&F6f^:Ajc&Itly\͋߼[9P8ݾLסj ~P~q;g=;n}`Cbo/z(3b pi@ #Q"7r촱 .ntA"&S܎2$^E;F_qyj?u8T <jl:ByN?0!'I:?mqܙxqm.Cᆪ /U$~M\e'CfoL$d_W'% *.ʷC;XhB!Ȇ'GLF%E|6zA7-3T %鼘¨θR֧u6$j 'j f=c 3m|KҤN!5ͯz<)@㲺:WC^_ab6u5.y9N弸:A9e/:#G+ :G4pU- DStU6WQyyq1f4r_Jk7۔mp0퍐Z^~KGA}L瓷r{{KW0 㫳Uy~zE~W2<+?z_;?nMeE~* EZ)C .1u1I\a3{]% >Ui!|188?\tU]&i5Чɸ.R6 <0Vx3,%o)62BTZN?j6>ygV| =+%KU3Od<)Nq߀aBր=\#y- D5z²KiRVrdBC ر"z7RD[?b?}<–>jK3/2Ȑ8|MSOP2C(X90U=S0;Mh$пc߂R'cŐjUaClun2.5ECchSzg䞳H4{dڄ/~ T:1d$Tqq] e[MR}mC1TU.4dۮ= V8F'fpR$ jR'%H(mr5\LƐrur<;p(J6`mNi# j,!ba3 e m;Z U ,^`KՀ[LTAW\-Edlg!{wz}z'qPCwx/wo}hYqCkֳb f9HZ͙oX*ۧ=0^\CϗӤ-Lt8Stk67Ż뜺΋/pM4TDqYNW3ZWM:$D[n=7t .pwL@jHGrD_4 7-m䈷jknOwV]ͻg+ #R欄wR;J8ԷLm썷IipBcUGM.Ms *ajʒgK!\R(rcC¾C| GյX}Dё$xYXځELH/£%/$IGݠ=C |+օ@Q["I@P`~p[u3'@G(2I ZŤj1+ '->`3=h]߆-Qf=YnKcQl"i{1CyDhC.do"@)_@) fl[iPlzep.ҫ|-Nx_a3p[<bӒl&ŧ]jY, ]4zkR54UTWqRU.*} 1 nײP>+ۀZdn`#ezKVQG=w!œlLC2ByMs3-Lr2^}uKOB4؎ЪP?>=K Q>- *fWKUɾ_-Y,S q*cɞ~1o ±3D<4b2NʏwY#i9IpAV9umi=~OO=[>ol/?_MmhYk |0_*cCS_h1584{\qU( HD) FSJa@3`%RJ݁m֯~2mIX8*S  Ą|(1 >=eߒjр) ;^@<y)DIO=7{+_bXDw1[$9h{΁jM?o\T:LU]:q=ߠ(mՓ|jZ땛$ό, Nptcz4tGV̄R5kd;q' r]I  &ZURpnήo]OZ bAEj^RWkW02F\g4{pT5sSGي1c|Exi\c=-[xx|ܳkdd5 1Q;qx$P{I[wc)@jŘl6?N DR9s Ġ` ifDxl⴩nSuEkڔ$r9?ݨ(8Xۏiљ{Z.I[;vn.bS+{x,xLLˉ6wCАKqvXM rT&Ox#LԢȤ!%WXmr SB"Dך: =7ȣydƓҝ#l 1)'4.h\iя9_AZotSU6T:Xkޏs BA]upíL9a~dh/6/{q!'~.ou}CEI@"Pp7I^=kt'* DE@ %_U #MYTSXjVjkFĬD{aH 3lv _9`$a"`Y:)+786 /Mp/ѵ ( /Nr%pnddlI8SմŠ.FF!޽\Bc'`fwO}M*__8.JcoNk5+Vz+2L?vPn@$elm]+7- ȥst4[Ѱk!cʎ&m>mtu]DL [fe:A^Wz  'J~#%21#y7b;AJA.‘';fG 0z@<+rKl4%Rf!xe1h4]W%1,dRHH|Bue6TOH.૯-.QJ3AWtd5[nt+pѨVSxmG[Hޙh~w<mFT%8Q9u<bzGČ{=̕zR2$IitV/%x̳]`+_)UVs )MDvW.>}VxrI75*5޼@=L% 㥑y1gD)rE:=OgCV!, )x$Ja}<| ď }*!љ.Tqlb{x}I]$ O-;&0 +՟w5J];"_YveQSqR:7~thuk$^L<U~Fɺ*FaA7~l}Z@ؑE&? Y\zgQl-r:=iȶ4m 4;v>dj T0215oN޻U2 Y;r,Ezmow+2v@)[JB@kaÅטEE#H=w]:@Lž3`$e6<5$5Wjw1IX՞pD٦>yP&ZDC)HK:*%b:J$0^87F@Eq6(ȑPj 1/KCˇ/If!իz[U;>j1fhر-X(/4Ek nM T%qGYLwҳJ](cI+O #\ /kԐk4<=!Q >UL6ϼT`—lY~Z7gVެZt֎c`ݿo034^qL8氂t 7_wg!Ձ݄GATrfب)[Zj.mُ2V;ŸI͑ڠqA82KͥB8Gp5KF~v^tS_FVN+ExE+5 ]t[a^+ (B+n {!OC8LF)]D V6!CO1TF u'!N_#UoȆu7}P6HyWQyMSN{oO,Us et"5C[Q#D.X4 VIC |nyۇmcr_| ^|}s`%h5z%eл$/S7|rQiA&7rձY4u0X %A A tٽS̕1[VOM'ak7CK$v?DZ7Av"~G,P Մr5ebw5kom=}71Nλz9jQ䁉} oZt:5Wp[(Bē/ Rif=u&]>5I3i ؍14ӯK鷜UϽI6+Vk8 9oQZP y=ψ44C ~ >LH-PDbK&.8`c5ᣯFSL y'cCj0wz)O@w9l(r#@;u- ^G8C>Mj gMjkrjY䖛QWؤǚXMR1n1,4!Y^Z;FH9 8I9 p b¢sY,~O,㕘jsk_wb1V ga)[ʅfR⒲$3 rpsZRuKIǒc< GP] )Me(xwIod\q1K %F S?N"ޝ&t Bn2p:뷕nbvGeFFqr)lҳLTh P7 >`)ZmTs'%NRdxF]4>bG>yU9 <`4U˹H:*.+vu<&Bv nAuhF# .Qq0=潀rogfyT*7ť&$CZb/Wx+5PHfȽ]\V0ƍ+%\q5G9;:ǢˑV!Z"Z̀ `Q- 3roy\\F퍆0 qy]lu $uy0-PCr2vR+[ԇ*iF<16+)㰗V]9$^"P昬xSSv:ywc08ɣt^hay#OiqBɎf7h}R@j&Q%$Ej?|\mN©3orh(y~;2/&?.ϛuo?T>FI']Z'n"`]9_@֣>CYG%fjgx\L]6Gy>Q 8]~ԈE8tFٗ[[*5shκog,|O[v)>O~G ^^Uk*ޑ p39ys \ϊ AjƝq7| Ou<_@I +(ޘXJI3^D\erCQ! NKm1c)0kw_S69C 4?u9viG/'#N˵k1@Y er@Rb=<+'U^vTR$FN$tyYPnJ&Q¨o\Ǚou:u {sC[VPG (>YLg5AХ]$~kpR$4@ sԎΗE S}Wx_HlX5);H$)E}ҞdK8:jclvLG?>TYb^' ;aM:>@Nk=^ap}ų?  StqmK57nmo4L6^hT9GLjFRj%'Bϭ/dIT6g?J 3^2 Q#y4Daqo{=#_0#ИOZE4 frUƃp=Pf"E<>p"AL'EOxC̿Wx 2.ǰ'9(A‰sb8=GJަߖ$M~q`K=.k ye@˜McCPȓZkQEkPC3huk˅u@Tw`0[?cNF!}߅ R]SӗҠuɢկd/xx |p:| "jP:>D]i鞀Z:Øfzl̟ODi]〛FOIgItp.*؝,}EYi@=Cvi !2Y5VsF XESOwiq]^79g̟akn~$zܵePC_yVqθp[݀z'Σ#Z7$;4c2].9Z@>}:vd԰FlMNx3Ky1!iOn 6RvNg*o_k L?řvS oHKc崥L}"tUv) T΄9YaU:H\ 9y1#Q1zw(nٽ;*U;_?]b l$'aqa֞{c=b8^<ϡ9Gηrx̄RdEHz]({|O7=B1 b~Ӕ/k@՜f .wݶlGr. r.EA{ݭlbop2T"! 噅yu'4LdaR# E^K;(׫aęLE5na8p&gU;}7 [m{\ V!rLnQ+fxxPSЪ8E}YGdSrL&:WnŦ;'I.pym0 \UjXT$gNdga:&NG %s U(P+֚T>"5G8fA|~!NEe4G[BޅY 69@[/h<V#cp(]q>nK>S'3ݹ-b8_# U/VjR*.#_ďwF;1.{DM8r\(,.Ny[<SiInpwQ#3+i||uWWtJk){4κ1Fࠄ'qzف` ~y苙c;$0TwsNk=ku^Khle~K<>- gO2ׯ±W<I, rA. R`BL5d/Ul:{գ\^Q  )=`d# uE,Hɣ~sNB-G,LSwG Ĭ[90Z 4 Q*XN15>|(Mx:DHFxGl2hQƆ7? yf͐6(l2<>˧F?5..<: RO '->KKcQN6?X~(r_3$=̻!o{=UfpW7g:x{WTJ~0x=gP0! ${^W,B{hldEHOMtd %hH3 SiaV"ksM2rD⇓LN..vFn"%`ܾfjoFX=A03y̢P!jg˅Db,d S/si\"Vͷ\"±^n$!ۢ>NO?0CU2>tZǬDo{3PbzW|9C>-YNƞg8c\<R1nkF;ۈU W6!XT 0ZT+[d 2z>E06 DI*k!h[]fr:oJ;'3y}wLFNDfDg:9AM Ϛ,qMd=;7@wtdygcq7;PFO;ʂv yѲAPK&TB"(#ipj8|4oǧ^9o|ö٫>/o:As`WT5z *.f0`So.NOD'r^~j[*hW,BrZ$ 0[8{^,K@0XkeZێޏ,hb2e)"8Perc`4MKl6d~t3#mʐM8<VoR 5o@$i9.GA'x*oM␮%`8^5 ΟN((Ǩ)PRQpj+v@fi X͐@D+QR&i8K%[ +]Eq>$^UR~KD$P`4Ұq{.A1Ouq$ Hu&G[ k')Սrec¿K B1ZR,xUf\NІe\5;bًr^i86h=IgWi}(Ir 4)45uxO./7|K~#>9$2 i {ʽ7N_йe<voG$(!%+9Q^Dv1'LY4ƻ x UwGo짱¯x@LMJq j >D&,l\ 0TV&a, CaF9=ȟPzq-FF>vT+7Gak9~[IЬ)cLϯ(8=nn[WXsApJ61fCWJ)T#…Ohi@u۹hύӗ@EŠ~nW(nm-C/ ͲǴS b` X dXf4|գFy,A>_|钣*hZ 6 %od4lŚ.z\֤rQW2p\sU"UԄGӀHO>b,x`K'7 'ZVzlG׌dR 1bpzVzi jz]<>cTrZh0WM.VLwzOn2]hb@|Z6nҞ;-Hȟ#kGY$+G!b@"&'FݓB]N"R˩|VpiIDYUfNsWbs°(ފÇ_>P:b^/|- rȗڑS#Py !Vm'Zf "f\1sxk(jU%>v/UPokbiO>l- Ӳ)X9=RPz:!8PVP6r C9\ORNLjWLcXԕ*5zmw*l k/tULeM7-򰟨4a {1b/7^ɚ1g鈖pX9w?z{տ  bS&yőHGξ8Z1p(8},f7x}\9;Ur D}PԖm;ITtHQ1ɯ#Qe1+.Apq=%DqjgY圐.ً*i$ԟp=Q0ۗq&+u ֬Q>qnX,KNcɿ6gCluQ |!Rzo[E'mك-D[u4Dm?')넍7:& SM؀6\y9pu^MgWWvjBWu.sWbrWTr>(/Jw?ҼrѡQ+ #X'v:XBbUT90%׆0rJZ :GuՓRn/L,Y $ͲlC*F[ )|c4~ Db B3a2OF e-ƦHn fwR} wS)r0? OlSHO!HJ34L@֚cAɸKV?xP:DJ`ix.%jkt,e9D-kpy]]JyQ/'9KUU%9[@Xɧn\uSJ.^o.oW7[9]'q:֦b|zqvnFn501ktԖ.ȱ 0W %o[\NPȊtQi,*fQy$0עj ?VTxl[í8nrj-0S뉝UER~ JBypx Ï (~$|I||^˓K]}cj^.)LH8LSqgHsOyZ4.ya" %Yz8DU@\~:]84"j+;#Iѻk( p*'8vVrDz\ J#? L: (L0 ﱀ)"PMA^,EF^D/6OWHOC?P|գ7?p@!c!'}# eg3 L3A^\پ(G%gAЫ/x%/Ϗ`{tuw⨐PQ_Ka'.6??1S`G DEvG-\fgmfkCjYZmfKjDn?"W?wDժa,Bm{N( lom}MMЕ}V'*>"2z݀A{oJ&{@~~3@…W,!VE< 1*ye9zO9H̸RXd&r6ZPl<-sx q bl3哀J 2)лƥY˗usaEMiS4Xh&M^_Ph|Z(_QuQeEuIN2$( V$ÆPhFYZu RLlPj9&*Y jZ\oIoMﶔ&]웹ibP7) #Q|%uk;jQʵd)3lAd$y :ύQ(q>h1(YmNm~~z'q sp D=F`pKvpXӇeNHX1\fWk-&#8eVs-|.O$dWpRVs&~=YX' *I١l&|9E,{|i Oo<F_w۟&r8[@[cݲV86vv]cQ5v"5+ybzbQMq3T y%G˭H? z(ׂ^ЁCs8nZ*J]{"Ÿ4QOV`$p9Qnݺ͵zPlB-Zh4T'4s6tV3Έvn&X^Mip ܹ: G @OZfFUl[LL4NrjQj̟& Q܉rq`N@f d9_\epJhhʌm~,뤣=BLXz8!ʕ~@|7_; ~~fAIv@k2/!RJP丘ӫv^jԒ{U2@IOOx-1=f|,5OO'#їjD"" 2ң0E_`V@|= C X"ʭ0د9ao PJ.ha)nT; ''] v 57րjssz\6 EttSk佲RLNHjLL:UvlHU^yq^]Ms8#ڲ2xz,8}uр9*!C̩:z5z/`FzD:R J'^c|;%'V}&\Pw\r*A[nAkk L36Vn7b{Sig]u6I y=:28Cd}B<w~𦞒&^,M C*f_Oru'heQY1AUbBޣ$V-_gԃ:KZ"evU)jmЗ! yaï8>.i'ֈFǛ?6Z5U5b䍯t8'bx\̱RyfM3Ņ 8];.c25&Zn yI=muuH^kNSncuy##B-/_VOS5=OX]L ˓6B!l/k%I.@['((P ka;n|êI^]>|$Q^R ; ċ}"f\axʯ0:!kkZ_ja[Tg0țW9lQ/ $-^=2SsVKT~?%"Z`:5NxYz v}Ba*w[pU =gCj1n'iўR9Bko5KD2a鷬0!yy9儹CO$.&l-Lj ͤ:%o x̉ׯxjR 76/J1ʵh1 Z =3б"Ykڞ<%a ;̐tH<&)&o3I̬MZ To"qWAޭai>\f|؛bTmRу]Q9zW?bSK`I:tc% qNl]KtDK/Pamͭo0[ g.VB-spk͓%H,0;>&m15쒭-|Bgo%eDKdC%7 -n’ËaCn"rsKʩU#kKC[C+~uR |g4m|޶ul ؼf,XucU묱Be-xc6Zmm+%zV[xoơ5"Kz2u$ p&21ū]l#ծ֎jħkF5uCExFVz"2 ׸€߹V^M2Y +g~"%rq֐~kw'~~]8FN\+/aJGr{:hz&J$1tsxbٽ+_2-0AѪ!Sl8İ;]߂rAey WKivmlzѝ5Iб0vJۓ3A%fv.o[%6 ѻ;s˓#s.N7q[p_z7Ћ#}̥>23;0./|}>+rߝ}xxfW"H."|r_ܝt SIggEpK ? A;_?z=XN\J;5*yW_Ͽnk n|RKe\7+G& $Z9f^o~ʼnx.$CPu<^HȀHډT33I1k|ф^L㚲Gm,L'ꡛa)VCM5';(o0__>$b.8Vk5ՑeR;*G ܗd s_2T (6sJ2y@8c"<J :;vPӪQZ%Z8y$GM#Y EY>@؊/TDnb Ndh"U? 1 s2b%X',b@3qa`vCC8(~ IcVj;-̄{}nލ7+TDZG &ʍS?ZlxEV cN~l~(wK>wcG.1D0ۯy0Rf6e-SM<Kap~XŒ 9tQn{Nx] x/sdJTzL lG&eW ݠùf0roe$ߌWop؁`Dn)0!1vX[.zŠ%]~4ՄS>nO6q5/X2זX`JX;HjmI_фkPj,28^^+–C&+A&<ꆨ{#YYY8l:~ VU:6(ְȖmœk>qcO,9b] "u4fǥ2q3߫¿>|MQ󶗸[NH l qu{ eI*b$>+ R,8hl[e%c"!xhI1 W@ & f:ɘ=Z9,(8h.6DF:N&Sgb G5$T暎ֻ99a{[~$%uɺIXpC 7"FgDUuPO7f?Yݎoa`MDzv]{L,GrS!W=^>(/'0!ԯ кf>ˀWMۡԌ}«ze'x~hQPM(_QvЏ悚1A aXągJ)G#av%>YvVIɎM2# Ix1â!44?@4S0nu:Ds45wSb~e)uYM52f579uolm*uԍrw2}4IrpA|j,lg?7=.QܹZr_tOI7u,kZ@U\`I^sZ-nWRNmH4HdQČ3w'Qb׳u/z[%n1vZJ}v FY@1Y5ŝ)^SBXǸ+q$PggmdvvN։BLI*.hptz*%)D؊/ 3xg;u#\Kb̢]ϼу*Jd]#kD.a+*%6gC)@;)i؇_ӢQ~[+ѤfɥBoq*q>^EL-T9ctaG%.fmN!9,cDׂ.HKRAfKΣ?'2RA7!H>a!{}Vhr 60cN !hP +|xla!x3*o|+Fқ>8 S5'M $.92b@5cwh%Xv^1ͼZMq¶bSXtnz؅$g-c\10'|Øtڑ(ev*-9M_{ W#"HQU?,]H}Ĝ1'_ Z_w%aHrZ{8o c!FN\FB^P8/;jE E,"]-3ÝDio (ƴltƂkStI*"+?sO&y4fD :ϓk*s()ukpW8 ٞ^8/^2L_W-g,> ;*Ls9bVŅHИd4_ ts _S!s Isjnq@GEm.';=GՎw"Y*KcrT+v630Ԝ@OWmD[Ա j ę#o ,3ѧ `g0$z4Y c$+6~ߣ~8zx}? N"*Ѩ#N]XP x@v~,eI2^,d;e ˫`DV #V喁.!R히(@]0{lq)Ѓ8|980d){/\E +nQ%M`q9PS<?Vd?mĩn<3S6_Pנ\ߌηOܒ:OYݤMhk2K^`1 lIAWDӽ[)9ԘnD$ε?UFV*Uen7mκ 5tZ Idgx$10G *b9٨@絍H)DR͊3߈k3Ǘ ^5j+idžHzk -e}S0/z/$dN [bΰ+ w( R*$0KnyTx4t%X8Wzk-H '{O~vw (WfbȐĹ&)-q̿ɡklxzn Ft[ )*iOݬ4Ni#e'@:uWVr.O[괏x]:x7,ִ;Ȱi/G=u{ bAlsuO{Uiե5phBr򎎲q㶆~U}] X0)g~|3䄓)~ֵWr`UHI ]U1ND0}/TzSnȋE^]iޱw1jSO\-su'b~ d^AehMki^^"ӡ"8En\hYLD-{pQ%oFe*#T9v6[K]ӛ Y&$ښ!b'o CBt2FsV\U—T3A+'..W+V颯i ,#o;zH*P DKc|s[q"<=UԛD3/t ej:١ Bٰ:@m$ kg6= )Ipwk1RQgA䲞t@Nᾗ&5jҶźWFz$=2*$|&ļ$~K G| \~1ڂNzvTu8\X^?&Cg Lh`85"W_~rquL.ƏaE89؁o@Yl1(e̕ʤ}q$ǔ"lg7yW8@N&2tcP.An{8i{d43,69xAjuJK \ v/8=2F$DJch4~ɨȓvP+&0EN-a%F@|[IOwHvƆp00(boFIB$o`͊8KyJUރ[:Q+vDjS9È>y$r ًlET'JSvͤMrc&I^E&rTzXZ ??XDP`{8OfZXLVYntԄVS:z|Ş8)՝(1Ĺ`RTZj"n3֞ !-1opC'Ns_Wzž'KF"TP/9g(Qtg&z4>{@*ec}-ꀍFg7 oϩ)5Xn7=lɄзZ3ԐFjlmjfG 2Phc'Hνuz,l%kuw KQK⓯3vk1h,0tj bLҰ/p- ,MMV)>f=}zt| įOɪyiAi J`HT8=IdG/BpD1 uzFD''Kb `Ҏ3K~,\Yp^:CAUrKeS}6KL4W3رg¤.|3]4c@ 䍗habyXސM<8<xttf7~釟޼GwLVLVVؖVA>lڢAqJ " qrRO5 I8Krj^ϕ^޴UGݕ^ Vߧ0~t~+hsILZԀ2'>0/?^H 'f~Z^OC}&&~T:J;sl ]K*֋|1:+'ؘت҈Úw!U.:D2Wr%%_<̖;~#Wd~J @2zAm/f}E7gs -2[]->9:˽X5J.X~#:sy3NӾ\fJۇ`PEȁwtbV-癆f] p;o/:\ZGŬ7rljS 'L)jAvs!/vib+# {hԫ-uL]{λ켣A'מa#쒭LBcuG6HmѠ1ۺ 'ݻPe*HE&"esW& UkDڧɋV{V{㍘PB{)Kʘ ze)l bm-G)<.OVo^4%@kZYd\\̫g2ܫ>=RYrT {'*EYK*z^Mw>%W }W9`/|x&4|?v×Vv~IMuQ$i۹rgxBsN(Q"i.|*@ƉG3ED-IC ;4~]y7 % "8\-s[az$YhL ]*5< JJܙ}`1ceEa#Cx=*e&Y{7#XWAoD2I,.IS&u ;%oI蟳%ZA\녿hGUjhZ,gI +%&>Gil;Ƕjn\v\xHckZ4DqtoR'^IyҏP.bC|xeCy x(6 ==YĀ]ZprLǦ?XYŦU@qQA' q >v LqF 55zt!hc#4h-YN:f'ѶtsO2CJg4S;Sp3BJV`3f(2cʵ12ocd89vA(7lxf65. "\]z>Vطw:-ʋx,Τ.U Rǹv(nG}օtW- su(݋I"3(XTS =%60͔̪VzJ7B=OKv. 7 Աlԁx0,1ɹr(rd|M4, oNbY,Ote21GZaVEoL>0"ZܲNݽ}F sVŮmp" Ռ&H5Z%mϺ/˄W3CgRӹ.+L>g:IM" j8JU!vϝӐzM.)j GA:]էC3DSC\S,>5~kR6 kUlo#-]-MJzQÁ3 X" b^idP[)T͙ EI-ܾB#kʞh^Qc79>nWci#f|;罛Ep yߡ8HmFb*Xi-FW yڻ p/{ґ䮎zԄT̄~e/bĞk|xlsY&-t[҅cMrƉriVɾrR|Ff"!%g*2= DڶzA)oofM Iv:S|BDpKm- O013wg?Hl Lϊ5D;`otcnhh/~.x?5.٬zA >fӼ=Wkb./aR#~\]X_RzڤV1ZW+B.cin= Y6hZ^LoܯDW5r>혍;шK [QK;ҖzG624"\hSϲ6DOovrYJ9E)e1-S`I AN3dk bV= ƇsLi/h)}!&Q 70|F٬ڸT Kj:4^86W8$$g౴ҼqC[HGI]>,(< -f$I`^-C*S譼"7֊aQp[xk\ :߀dtɑR8 uN\֕!(E+O~wģu3 [F˻N UX{Cϟ=f==}#aؐκn(&uDᏄi/!:_3Uqcg&ʻat)Rͯsf]:!|g :_8`$Ŵrff)>B֦3@ON N2BZFƪcNMa[3k{[ޚ/Ę1-VʴPGǘ=gk>c ,;R.fF6qtS0[k*Ciq4.ї)X~U\|4_d ~C>}T\} YJ>da+߻K{gBvxOb  = "$Ft6A_cEamXe9io|-r )?dP ɭg` ^_%AyPt:LIy?8Ks~.$$'`=9Iޑ<8nqѫEL+/I$>dpBX`SՎ]0I)^csE2|V si/^=Wn&|sTqYx{j@`Z$ǑiɚإB}"# v4~PACƾHc$'cLI" =}SI~D,j9J7vn&UgE|╣ӐK\Ng@͜6w]{ԉ/XCsb1mLi>r?'[Lt(=lR!q_v*7g`QRDꖚBI)]R?8x!oWSଋa:|T\ =ȡZ,.u@֔1[iEJ8ڔ{2$޹LO& Zk8GS;.Mf2 .TLa$K h!yؽwaYfA(^E֏)1W8K`6Uŋr@Q\(+0sfe*{th5~ô>*T x9~gr>hYm[*wsQB"֘X=}w[m@/o(eE}QENdl8U|`]H2Q=jɵEH\iu ęj=r]&~d|\emRk>C\cYe%{}[E"}V2GЫtGCΈA`T 9ǮCڬ0w16 }3YZO\c5買sfpܚ[4˱nQv."fjØX+IK,j[2-PEb*XƅfE}s|y"zڌQ "/};JRMw:%ץl&J`r'Kw 9?ǂ#:gĜb%Z_I}fkaw6Z( Iu8mN׫i >ځSW6?\l \vRģp hGU | 3XɔI#&z V|dY>04ԄNՌ u"qd+Y  |[m `3*`hQO*(7I5+8g0wfj߶!$(P$¤$'w8ўϹ%M۳GY~۠Υrr 02Yj)c|m \eFU1 $5#f qNQ3ʽrY{k185֛>OM<,F~Ĩx[V7V)zTzu۩]] ٥}OLFw1T`/I {=iO SDq2eGTZF3_9{q,.fƤCUL4kVf(Q\'M^ qx6PXToa.ǯl,gb;n,-[VluT(>ФڒhewB1 2Sݕz"0AߴHg01rdp#/ݰr=k)\5$"81{BG?g:T~D[X]'}'B+̉!uϢ$8xppݐ;)qg)~,,ZÙe0{żb\\$mbM_~lӒ~b-R¥vrppnS$Yj/%ASY+edZxUV! 繏mGmqom3'3|?>'w9w?}.@H ,e,7 XJlZ ~pJ/`;Ң).\Oq6^u0S~ĎW׀\+<6_u~JFU eJhH 8y݄pnYrdwj$-'}m1"}mw2 {|4eV4U2Jئ4EG?l# ȥbȌ(~:Q-41D(J+rX\HP!8`] BM0y퍋=GE0,l8Ą "Z"0|t #zOfqSJӷ3ڨ)ԑt v]-`Ĥp&_2R^B2wђA"LR| }۴(l#1=`y%WMc՜IJ:fk|*Xt7ZhBj C(m _LT݊LYEWsw.aapzTP|m3S V4*O>@h[#RjI@wp<2^:Q5T_JY8τ‹!.\tRЭH5Rd!su3ӡ%bL*IvE˾ؙ}}=Rrnfbv٢J̽Oe~/vRL.8);Y^Fϟsg=y@ J/-̺pCo^>M/l>g9Nb% K@n aگT3o,6G|~vʊ*w2^^Gj<3dXG/Yܩb'UviZ_d<`ܔ?sѦ˸\L8<D&b72KJM"U% -/.7 ?{Uox)-o\x|@eP!7gu>^`%A%dM" '4p] }a,v#Śp< %N9nqY@U M`t+T_FQ=W + ?& b-j6g>Wl`D|)"=(p2$a] L-9tf1T{!ą3GLWM҆[oOgp[oX>ȅYC d0߳ITק0kΨ' Y-p|S5lg' ð\O ?(ѫkka _)7<;IQ+N8n#3[GL@l1P#k6h0b LA4 0pqN3k!tG>W#0Xkѣԕnd*2_dJO84舾 Oyp4;=RhcQ, հhn0bIH&2c#qO70]B@<,0\GDV0[1P03n3!&Pi2z~Ƃ ӪFcMW}CH6LoZw +_aF3[t/[1d?]k]D؆' NQx%|6(}svD6]SA/Fʵ ]\d(8e C.ͪBe~jm2[1UF [̰{zu1$je 6-5꧰C:8C3.V]5 D7[>~Yp;j,N=K4+D )zrm2r6u~̵6Hez렜G]c-Ҁj4ŤgMU<"jg[VP+ 񞀲>W8;xr4 L\F{'tC[ -ۇClǣu^d0(h(2EY)o1e*{QꄰEq$H A0^vMd+ij9{ tbB4dÀI JNs~3.\TR%j*FQxK"%"""/2ITAԣ+;Ƌ5PRϿ]=ֺ?Իĺ5# ZK7 .,#Oת?s9Go2,*pZ HZD5a:!E:?fاKїxM*/2UG?. PH `z!TFAA;G`:?y,W1[wC{P8%j 5ki.5vGжw`\6Q86!O s#<ډW#n&N_#BNW4؁c@{pM:ksF3GNX]1}0w VN o7ٔ#[ͅu٭S5ȨUR7U&׷`\~]O $:DR Meyl }*#˯T`rr.@7L&w )<=|%iW+ʈK L"M12"<0۾M~3B?ojs}ʞ@{s f&ѭlDžۨRj dk] zz:+!M˜)}ys][0DJ p7CaNzOx@ڄ+nAXuY!T% a˃ irq>}W&~pIu'yЊ)$(`0 ~*#s &n֪cbMQ"0" eDH0)< F)AHp.FH ٧H)T[N82S/kdM8%Aβ4@9<=q#'qy5W(# m'1u˝up6} T5*4Nxn)!&٢[GxJ 0X B[` (m27^8vi0K&8;]'ЇeAfKNႣɔI1\'2* VzUFmXˆO / JVLmVNJ} F9F՝Fb1j +}nR@d oRy%. )o+'~bc}]`%CvL_KVNZjL1tSIU"g>8 =<]FT* ,]exǥ t64JfTCR$<;ҫUc\ךt x|>Z:Ǧ9Ouה&ȂiRgb9#`~x7RfW F%3S(E|S=?Orұ/t}US]Џ^|st eB>f[L\i z ,\{EᄙiE@'m>A}]͌Jq=%o*zՠL Yu\zZ+x{ulDKˤDGGOyV( %1bk`*تAq&8s|"ź]u}J&8vwhazSU +؆H > n>U|0IzhOKx8~{ǔj޻>)5ܺ#rzXZfC(%pl#ozNGqg2 ~uB6"mK >%kZlQٳT@+s`1>0qMP&]%I\QO 9B*'!t")f*NүjrW&Cu hc܈$vID`OG^Q?$}XK~-hmOF>/MѾ;5`|vG=@L}!2l-Л$<1DJ}ZHбWT:.SoX\QQvC17 5'o ~~G1^KxOޝL@A1opẁB|4~Biw~UZ` n+|cQ dM@K>1Ɨ |\n:Lٷg$y#&EWN_Σg3~4Kx$P*ņVX}8vÝ fWK|o&C52P@[k&,>@F!A?SRFsQAԌ, Gs t Wt~9-@|+m^]_O7I:{k$}V@6Ζ9e9Jܓd {I,ď@P!VP[(4Akrܮ2u ɃL˄_3XV1/*e+*Ԙ1XTӪ&V ]-0NPPPDZ >_ ^qp4- ?z6}~Z ^­L_`+"(jw]mGKc!Hξڲl|H$(Ao?uiٓ]_n T7ݦEt;ڑWZnnSq䆍&N hψERj ]3p50v)geSdk$ y$uˑ!L z[miSwo'44,`:`L<#: w ;ns}_Hpug#΅ UnW%w|6b6u{4!\ y,޹2&7w9| g"bdǗW#`t'B$#b|U3YyM$ U2Zp45o]-|a^-oMWHK)δк h}ލ&{ަk'ʗ l7_yR8mQr$C %(- F9jf2&o4A^wc )sՇAspWh@&ٔ]d~@ѴiWpk fn)hԤ$ikܪFBF30dHY/vLw5H5imEj4`G[)ij\p|d%uCY\o]rFް_,9 <Ėn6$B=|1RP 85]:KĕM U$ 1}̰J9"` []MvpN0+n/=l[Hl)1 $|ifm0x<&>|{6@-[DiC*~J$#S41ux@*0'QS﷔+PM2uo2%EIFn:052ҍ}z^-f M$ښ,Vw"XF6}vZhO:2c-wTR nkX G'{ HR3s%wzR%fZB\LnQ18ӳ;ֺG9ֱl_7B{Qf DuR1:}%yr/[_:]%z 'YUNxy;F- g6R0^ MF3h=k6HQAKO^_@zӪ?931te9c6,m$tO& 4 E9uZqɴM .<4ܮ96|A$8֨`wrBa|e|¡n{Il<9aw L#^UbAٛ-cBa%Q{W7TK֚HaO/r1vĵb(=fqz/)mYW2ۑ=5 T9UPlq=Rz3_9jQ%*"͊ɗ;xS5#I'qp!1 MZ,X`lT!h<6Jچ7Λ+qCEvة$=R޹p]e3b=bMPƋV)cZJv;*,W0b Z$G ,6$ jU4]=M={m˓E_gr5'gtP4Qpzul\a̵P[AoLU"J\? &?bE^5J0 A|}(J BO3;_Gn1-I~ժ؆e9sٲDG_   @ Țd `f {C0dW[B13I '<1'6޶_i>-X(.!w~zL@#tyxo)iuI!D!jhlD؃Ρfݏ&ܑ+B'J@xX ''Y ^p '\$ US'^uJ#mf!CHh"IZ!+Q,b[XkcKN^QzGv Vt9k}rvP#Ŀ_]D_t!BEWLnRU 3.|=DrSNƃO]T@iNNn:GMVUQD@-W!h1ÿu S.JǓ7.{q:{A .=|0:pԅwf? %)OɮЀa:$}U.F赀Du7'ƹc()$3.L ^" cɉb35G=k.@RGsTWz~p愯v-yAg0΅S>8AXԼl ~H/{xp%!Xpɼh\ H+DTzoZ'|FUPR_ҍA8Bl٣?5]>Rv5?|l/f*a+BrG"I%(s'?].X0ȿxM0D4mLtgD0 Au8_)̍wo'sŘޝ 㠼"4:oqi.RzgiېvUHcr̥SE'h%]1 v3:Qmceywyhepj-pʒ&mi&zVP` ZHsuP 7 "qgp; AvQ"CT fJQ-4T%l/ ̟oP쟉Cv1Yjk>EYS3z¶pK5|2m:ng"BA^Iņ$U`BPk8.OKOoQ`.uBcB_% 'oB=r L|@ OҬB #.lgfo)Bebvg)~-*nW._Et1y4A:Vg] ozgTHH&O+t1LM$l]ᵶ_:85ɦE+t'%Q^!ڬo;-piT07g$xO |BV bC=29..PN8ujސ G C+a$"bBYL02e":8AZvaP-˿%uSF! =h %_ul2*&ij nL[D#(uةr1M-B- @濗w@@UЯs5Z>-jĞ"4IbA UGɺըoIu\l\ 2ٍ71x *$QrP#Xn¿x_hͣ!Ư-+-6p xGdO7i9r!DÄޜ %iڶ6rHweqyJ|M+'BҊYϘ>HsIdι͍: (G)~$#M`#DGs(hu; 7hF\Z5@3|r2 R9C/ K /y(zv#:E$swg/`pw*Lcg |HF|'Rh/s]Bv_Y&س^4-tcWOwͪpiw',eÖxWx[&Tl'2T4Na} Zy4uQAZjaRG, >&cY#6BT!JuN# Αea`xoN5\P$ 7dnXTxl.k2i2h?X&iڦ)6= w` Ud&Dj$..bq#DFDUXi([BM; hd_~~^8=+~e)@| &3f%/?/[ ޽^^Nݼg5Dg8nwjߔ ,,רqb!*6I/aKQ= PoG׻͍na;YQy[,;o/Z z'(\ePؖL ;3Cy&qV+G^5jϮ8ܽ]h!o1q5G0xoZqq }acX`_[hgoqktrmR[K3VgR$`&Lnnl{c)m"piÙ|$;OY|+4HwX敉2SGAB6 {~($JJ?Qji nE}vFl EH-yZ9G"Tz{ICieֱ|˖dpr+^𭚔TgxXuV%[mfN%N"'7 ѪJ Y)횛z}^7ᓉ6mi%t2K[sEj+Zh/]ݻ %(!"X`-URȲ|!=h9zB;i2wA~o SlKtɁB6rj+|Zb<4Mja[ѾHBjђ7MFGV{^UTLGFlE:2>69Hq+'OznYySH|\{$62Vroh\+ 2GyDE9 /T`%Vڠp 5d)mD+2% YYQc#HĿ̟k(e]$Ҝ[_m3~~9*gFշ|³mm]5w`$hrgK`7Z78q6_;Ҩ/jADarb|V( qWFYs_,fm808w^9gdT8J2tki#]]+*iP:.`$֠9Քt*-Zj/ ."IFdy=iWQO+q70D'M;Ќ>h@r7L]l(2ELYY=yxnGx(h=rYNP@EʚdVeYUQ{*AXdj6NX`JӲD#^U-9\m2=C4{>Գ>y[U#pdJNKe#d':!=emT?V.ݲwX1;`˴þ7]*t{P~p\ C< MXr{2Z juD ~|s[Mn]d#h3-=l&ЋPSf0ַ\[P˨e؁1c.>aҮc硌0OǬ 9p"l$=t|FN]hҤDtRi02hG@"h` X& ,bJ\ RwE3Ёtݪ,(SQ+ŦR5+<ʇ7L!h>ޭʟɉoj3ְ4-YN͜Jc_3Յ-g{i[ sw:՘߳yHXSQ J.521 KhڥZt F ;~ 9J 3T1"9*#~4)Ԩ>4:!}w)oB{1DPQ0L> ,w5Їw6w7_R1 v 99TE}iy7ƻk)7zquY|ևNz9iNHZ kOm9|r t"21Ak:]5Ѩ-)թjq\ VquhR?"Ӝ`˳zwnxAU&)-M 7}WgYqm4FT9vO9 {+`XӗWj߾~v#&vlooBO)A~}Huϭ׊4OŹ&Mf%d =pJg>mpcMWuUHŷ`CNEZEo`nKcN.w P>/oBT9EGBc)q}oGE∟E{4\d"ML"Epb;?j|텉|NŒnea uȶRdma-Cvז~/j㳋b}qq=Ms7R/ :@CŻi5*\Ӄ$[?ݮh0E3 =Jh{臏LEdE\\L yOIO>HiO;MӋO*ZtmҘo`yǰ=>)t8~8j(j8*|<)VZ\W}޿>.t " ]v{XyIe_̽w=z ,oX$OfGNw?}r:{b9&{Ea e %nAgLܙjxۆSTg\kHL\\d 9X1p=ZCf氭{e2AJʘeo=Grϒ xg&<8h!V5WIXh ^O% (&Ff!';ҿ]gZa^Kx>w)J`=F#[7Z3J3Z;>Y:9,mFY'a"fSf6;u5&curvas\Cszgi/m'(5qj-ߴY,dcWdE'&E?4ةcq})9[LH$ag@;(~D'FZ'S8 :˖-HON$Nb>y Rƴs!){EZ\g&!dezo^,|f/Zn(7l8S?tu|*`.Z2u=& ]Oá ` `0}aT#"#Q0 Ub7LG$"ijs^X:R/IV>R^𕥘Yù!Pv[\_ZE8.qlׇhW3#ZiZ~7؋bh; uU_#)Kym%kE#]C``VO~1} Wg CrKD^7^ hBlʱ\UŜƭVʜ}2ǞaXa86وDiJ ŝ?reN*;D:Ca 8c|r'cҨxMVCr w)ꆌAX."|9w{ 4NF  Nڢf-I:(09͇=Y|Cfd?{Kpx: E6Al罭}M ˼'IYfi]f@壝6Yn _zŤ5@>"q`{xnY?4H Ps.yw.OL2"R<9j)[]nnKU-bwV=(ms%>R޳iUKIF "^1@?yv$>UOQSY9u޿fХ|d⠯?:sM™G =#-&FZߵoSTh2t ֮Z9Z!]|AGpWtW$5NuZx|NpȚ䆬:g6.%@lNAop߽[/ѧJT!w[ /ەi|o:"<ry4:\5r.8QX#S{y\mAzBAv?tXw|7"+rN~pօ6=zd`^K7\L~Y=-T-tğf<: J#L٢ݍ]8"}WN8яST^A@oPj.PbM .'Ǒ_R X-diw}nGld i:_TV(v.Λk/U/@%Seٵ^tnƧ+&@跿̮ŀ5.2V Qm&[*3 Ȯs'䠂xLyf]S.qk@yZțo$S meGmE0Q[f7o+yPly3{ e@6[Mq^r?ٷo :]`Ŋ`Ŏ"_d2z%(0(qez}7)ALTUɳKBL-@b#Eۥ'K4rDUBjgN;? +mj“pQ׍Y&b)rI;(R6McJC%h@_qf0࣓%pp_4WC jaFKG!ZƷԛa,`+3ҘKPn].!4l=4Fy^;)7񽎭!~Szv*S|OXAVlXnnwW 0T*12ߦehfrna{'RZ [䆱0魸cH+/;mlbwKxoZUmˑ\[k1lu||rro-pZ=)cV3D}8^*zrm-+,ÇoA:j,nzZ(kӹV+<#ݍ!EY|9Sa]\ *F)zxîғ7S\e}d;~!nWVeyGΆdϋugv[\m^;Ue'RA9qmhqؠQl1+W]jݖdyk;vK ]㳜,;Esߵ[U4OH;O;KR|z']2'7UQnͣm5;:s/5 :܎V]&s:_3GMd|$>:J"?Kr8&=xb!˛KA< J'YNBI2W'3=0zvn6?s s@M"7j@H?'sn֪`BXm)d. z)  N6و8/~`5Z腟5{  z,hOxb@2Y!)?6<*;:> ۳K/߅k?`bmmp,0#fQOure0 ]_Ȝ^=nQL g4at цy>̙-uQ4+=^..2o wp˾{ol/\Ϭ14I8īH4MeJW եp(BKuaSL RY-f>O̼0O,2twyܻQuQrp!-*5>xP2"$ƀXmlᗴ[~T `v]"OZܓE= ~05H=z:mTj*R¡7~]dW: fa8Ը9t|o`zCz#j7o49Nrp*fz.Zɛ3--7i\ASAu4*| &ڊ\-Gcozdk]~ZEb'EHxv!BO'߸w{9;=,h`?P"聉t糫nCsnrI?$SNۨԃI" Ǔ=ϿA_R@{_zi/H3߅ݕbEg%(~1gT#D A߄{kq3T=kf4ēi/䱉&ɉ'n[,mAiKXq\sxNCw H?OT*e-ѣ$n˗ a9˧u{ @99>jP(ق`Ν)0}t>\>݊գ`7:e~բ/ D"[t0I$wJtEƫ2Hk*"{I0R:G2/+WFPnh?N mɡ!,K?W`d3n,<0y&^ILΐ,1=`4 ֲ+O#H~k:m_$v؜Snט;w:2049 ^ZcB1>,JvD[B8_Ro:f͑ilw/^ jN`NG B.X%.Zz]0;fY$[.HS  fz]Wh+4y:2.!GξPdh8q+\νUZ(Y1~I*5V69\`kO?..N_e;Њ,N/ k :M)6pyՇzY1Ir.1Zoq|H#36+3{әsSFY_HuoX?hթu+7TOq~%Ѫ]-˛։~+9\طwi1m`|"!Ply9:VH.qH]tӃے&u"Y`L/}u8Zoִh7^zi|  K;,Ie+9m1v Lqp!:Hsgٷ_s^/Pt|,?D .$PsU:P>gª,QSotggSҢlrWIZG/>]d$7<\iԎRo> 8Q %l3IGpa;9j[Gw%9F{;{juU ψcQr!' \-LDfT̈T}PKRfZ}$\8|H+ /Z@;ێح( x2ǎNoB_1nsKTTZ[O99C[ײ $p`oh: JY6 r2^uQ}⑺TXrLӀUI(Aw䡻X?G#n󡃽.x̐$w,J ^DA S" X% ! #ADt%g A662p!1iKBnJPH$˒+ٞ-ǁ" V/;b fj۹CѺX7Euυe]c-b&vO6s߅UUg#Z.KJ1y[l}vgs#0- c퍥}U| $so$Ė ;u#k[1D" ;cz|_52hZUIzn=#1ۗ+-5v.hRP/1 "*^ڋrrGTY$]5WE5+pnMu9_VWYYanl*嫫=ݢlJ*$zM2*fU7 [V=6*Uy{%?T͢z #$0Ȃ78(j09+ȕ F_|.i{zz p?qT]uYUK@wUO?ov1j>NOO_-ݞ]c/7s!Sc7x7Q*0jrv;Oz揶ʘ휫IkYOO(r zqQ>J\=S,iG_|:QYy.NEOɓiUoB6YE0J }zOӓg_|IuqrqVqJ|n7ۢ?gdTŊOa^`ZpWsB0p ٻ|fKiB3EwR|eK dӱ&ܗiG4)G f6 }U&ɴv؉taZX-lCS'#c:It|s |q?k1'\:ijb[R4@RXckI?X(zr3B'TOގSZLNHBOeD.6Rȧ8\-!җIT:9:z׌fE΢PvDJ]-PLU-Sa-l $3j^I(?-~04WSv`mQBDz/VMYݾҬ$"w!:y7~~/&w5.PT_օkx%ʭAѱ*_qcur v*z?"Ѓ/ANN Bm'Q'<`w4˄]Z77˭g+fT4k$:2I͕ң]C ε{$S8K*G -;nz`n6#B_L2b'@Vۄb7J@:"-8 MeIXi/32p.T]-&[&qH/Jڝ XN+HC\(rK*rW7az5\ ! Q~*  |.{Rһ@~<5*)\;7J@.!9*&( &T@Aw Y0{=@+9@ ^o.ԧ2_cz˃4(CqI4 ('DA#@wJF'H?m dVYք;q=2L%]":Tnpt[aݪZ8Y YU5$wϼs{5@:!l=m]>'~y;zYP{|l} D@m(roRi}K780z3IoA-t=h#~7ܑD0*N-zP'P ȥayy&oe@%K1OhkS&!Z2v`^a$Do7ڪ`c/{hu.9iZEHG՟עL>*8R' N ^\TpY[:v†W%-9K8JS#zJRߟ?v=9zFnxl,{H[iRO0م>Y<.'Tc:=r_6\3 ީ,<=80qDA{h^wʛ _7Ӧ &$"ɪ93PVh| 8Xs[Bn'**ܻ2!^wUpڳX98G5V8=hv;MÙ茧A2@34iLY$@z#eWRu4wKae۹@&JrD;eHQJsTJ=㲾U45D%vA374nhpHHͺɲ]b>,"i [,,I'-kbFemqk_"5DreKiJ[L?i(=)ٽ. KGњ!U 3"΂zmo=&x>I&@*MwؾɔY&Et'hn1o(|VI[EdU 5a:PԺڇ]TFfۛKab5$ B#焊qJN,`-\1צ` Be6-ߦ&8},WE#!tTmUNF@TO P5ۂZ+/uX!jvc|8IdH>NʏŸ8 Qq1Mqޠ7V祘XL״&޹Y Wxӟ5ёf9#zLNvuʖs!"Hbζ?Ň"=18VIEt̬.3geIJ=]t |%323 PKrN ЊUTdcVo^!*\CrϽ^:@/liL!VrwŌ4˘V-d$lD\w"^/k5ثrqm׻"]Nzf3|UA:C%6n-̡7rH5XB]Kz|rv| 6_Vh66 J?RZ&W+@58LvQ~қLCU,dy5NG看J^,}+g" sezÃxAsT&;Ђ,60q(k?>|h?QxXY"Fes'Q ܭi!ȱSC=dh`4diX{8زT4?8P<.*($AORG.Ƣ4F<>DŽjS: [e ⾲PQQDlVf`"Io*:%EG:sNFCեaܝEUSZϜKgmؚ7N"pυ$HYi&Iy^ߣKd9:Y}'}*6k-nd-@?'{aUH7[or¨(˯0c/8tЉyY`ew3/:k}Lw,b1Z(!5nDf˞mֶL~`Xμ<4шLH-.5 nz *i 4yF{ y=(<]#E߈jo: ٷ&ym | ~d"پ(ZL~R. UQ$y4􉎮yh%whD߄u} <>N^eWvgĈ{}| b゠Ao6ݶr 0"W>]IHSZH#ty#)@½œhʡuWr 6៪:C;Y3uaƄEQ檍 -QPH%7][K[iZ:bG|!"c< ~p}a/c[t4.mjMӖ/lb@ |PŒ J.շ0uH >ExU)8#]!Iϑ.(,ږi;y֤BԶ[T3XA]Gomom+^#,\@>];s2`3qsxcI\:$hΟk)I?|IMޫe| {=28ζ[/tvRi{͗iBИb4PG'}mpt4 lŘovK79]ٲ|/vokpDʀiM+ t8_I ِJZM]9ꠈ;*6p=@L#4cM!a' ؜lI| z$ $hdGí=`HbJQzE|\_@n)> q,[=oҽDL{0(O"BnvbL6DC DrʊVܚnZlRta5>`b:w=xcآ1j(PM$E6ьiȭzVo;T6J0GXMq^('""` L;C^Qt\kթD)!wӕ(Z05s<=Ai>'/;(LMq /ܱDT#X /.#(q<ק|' y ΚZ+_&ZH͈)[΀>6OCڗ +H5E:+x@y)J Q?Tt 7i~Ɩ -"{llfj/*¼n[qŀSR2LÏ'D$1È̎If\hOFBO}- ( xr2/-2J8F_"|8FC23HMat}*g${z_k[8MDed5Mܸ)wNya&I!L:֘q4pLn )XwTTK0'Ehm9 pFo\[҅ f8` Jԑ:&Z}dT]s`++ݎ0LYq(4nv>\LQٟ|k'uvqYmv~AvqxfngUś^9GdYͭvEU.f~FݭwOG[4^e?*5OO-*Ku:-{_?Jiä.'-Y ;U[KYhB7%6dG󼊖ŹJ̼&-`d&[.o!Uz LӡAK&x̮I=C!yh&d $FB{ 3alzV.N7Hp`h w~?O9F؍?:}u>5cvW8) ℮-Tvzc|ܜ/o7/_V_+}\^B Bǧ 8}?..'?1T& '4 U&ey ȉ\UiJ6†0.LAu^ƶqʈ9Q@!gu#vu7}u(E|^2FrS\jls}]LX O3s de%}gd^^;-8e#%g8pRw/^& OW-]-Úl0r-#WDk[Z*P^/>j w8V9 #XwD GrmSS)WAݐAu+pA͖~<^i9,7:g3B0lgqv- e], F,nH|ؿ̵ NcIfnI~ ƍvsUif,## MIN`JH)yr7*XUV <Ć@Qp^ J?/6^vEMޔ螳Q3vFp!#v-א借ݐ)3'0=diޠ啞%7~ݻw'{f>:B AW'N7-f_<$߬oV=W:)F I [$nbH#Q}Y5+gBwS::f!ѯ( [u\c%ɗ.yD#JrQ}AjFS!v- ߕ xĕ `Or5&:6U!)rYkykg;$FpkJvJs6Ƣgo6s t;O tfre7g%vv:0&n"Zg3@/Ys3͏ʣ]`1Tgq.xtqdbgb#!Q_DEIe?@G7%?(n- Y袑zJf3vHp^xAfig d[j<$3I2c嵳_wPz&+֧Ϊ*; ;Smքbx Z ʭ(6)v=1Jl٫ Y:DDz RzTU C -oMop% ":)ܧ`hy[2'*0zCjҶTi}5z*)z//\%%GV 1xF@7pcA}r1۽0v wn ÊlGѓ/Kli~2yˍj(*kV<>;CUx&FɳO%ӥ+x|sO8+'ZYW]0*: "ނ"]}aY-y@H֛LF;Ƽ6κ4  HtIBM"}{ *\ `IR2rSrj"K4j ݠߤkoVo9 Vt?g=)LJ GXa5A&$vQtùI}^6nnTmFÎ^Fa^Op&Oy%??5~'??v*uR#74L]rnWqXӲ@oZ?(L$MAhQ^mN5p|GS 6"` >Pl 0>8ʄ+E:~1QOF_L&,-' JR … ՘Wx_;B${@se ;۷p?DS[Zip+H&atܙ3 @dG@gdtsq6<#%4;+q(C_f ((Q c@.pKY'Kk/u NIs{9eLaDbgHbNγ͑kAn4أ_LыxI8#LS@C%[lLGk])cq/BVS\c]u`KD/qy~ٓ'k ۢS;JUlO>HN.\` [+e,0Q[o/ݧ!LJް ˚OPa૪ >Әvxm  (6ODScʀch?V`1(#G|嬟D d܎i$SK삯-}Ɵd39e#`9' `y|,0`>v<29 孟c9znQy'Qߍĩ X 9`'1zQ<%4x_፜(= z0)ĥbZu7} j;5y+D%NcaPXq Yp,Qzuo^s:.!CH!f5w9俣UXiH/qq\}VcZOo/bT=O2W٭h;ر%Q m?5N! #E+P $ o}zwmu1> U[r;Fp)9-vv, x\y$ |g(n fΠ i؄(<do+@FbƶYwh̰.ρwvG͞CLfE`6}(Ш-fVGSQa6rr1)@SW"I, XլZ\ ^5BUG*B -!J4鋫'>'5қi%O#%qFS.ê.P1Vq7W- En5h"!:c>+wHR:c 6M(F%cwDB rQ=+QS.s w![ʱL>#y_rlß"n;EwΔd?[6Ӊ pS]_Vd%mԘ @S7K<=IjoyܻNREieьL#<6 ]*dŚzP0_y|[_?-KؐN1~jFPwPʍ!ĆXcFu\js+Are- .)E^ q.V1.b̗j/"\2*3q ?'iaS^]Tv|L]EN2(T*mRD_O,'e|#HxMIqP-~+#.ҜªWfoCMԥ.D߬XOdE Jmh^oл|G]%r f aQ! B -f*&Y#e*SL$Ĵ'ͪ8"Nc[}2xT D!,g|ع9 8,ڋ6^p0c\O>uܘS:W1dz3|T5݅ |P[ơ4U!a:)p<h39LP_1Eg#j|[&2-mԤc='frxaݼ#ob~'Q4s$­`d 2~nDJ0VDݮS cMa1ו.i-kz8 l35z Mb-/xNַ ^듶7{Ω5]=9pjIO w0bZ/#Ua\A : !V!_elzuˣtnUAUu>oxoU%ߣ7l=t-R&g3#vNyRdIJihEaI yN=CO 9+TOf wKc#Pn7 ʾbZ2BIY'^mVjW0g`@Tc̺,.eF1Z^RA8, h3-꽯#\ppeѷ 1O5%da-VB,Q+vd@6e>1CmZ;mGT* ;9 r`:ǀ~[u7כ)VN pa +*OlGͮ`C{GLqcّ_颡_JNsqe2ww!1.A`w-Yf%z[&~-l&j8[J;w~ $F BCdڂ*otɼ^ێ\0}L^1MTF5 l~Z\)E -y!C}N|!ЗICUÕAҜX WH͝iDbE͙@3"ZOa`\P2GxF~$F0ř# ИRƫ&.Ҁ`-KqUgwBIWELJp(% чKAp)O,UHM8*ᴴD6yC^ĿfhN̽bĻ &k'3%wggԶ iGX0GFh$<3 ۏa ]SDg#Û8y>la1a`@J OБV?9^)L>SׄҸ s *UG X ;n,k7;8g3?N[sѯżU 8lV.r\ĵޯ< MҸm׻f[w)0itG 1rĨ;X˴sT.>[}v.rogP=/(|: V½cLiOn{>1\U)P]k뵈hh|A=J`;_9>E.F{=m̓hEd}{.ji8\x 9 CtmV:wmT0mˑrLcmJ10S/޳*"auRzɣ)7)W7x)ΔZD\oL2;)7u(E:[Ar^KU;"X .&Ա|FѥL^G[nG e}ZNd5gVܐfX]jvi@da鿨lE)OI8WSe~&-+M3)TO6j̿#++F)=+EAC6 x͜/x9(+4_kl%6 wxw!Y̠m=R,a?L|!-o UWZ<>FVEAtg4 rAduA/n$SP&Z68(،tGhkG2#9y*~ VIJG d&/=Z4alߣD,%Y5 |T$l-lpu2р*1-$F䆭Raɑ8HGa rwWCytJKb5G.4û:wX[)۽ɠ8Cy\m]9![k/0[PyWFi\ |wz}|g7}p/vLmB1AeqN'n7@'ˬ2($5~ 22r [cَR >?unVsݣ~D*n%ximԎs|!P$tC>:9m Bz4W}D?>QOѾyAb}Mi6չEw(P&6 qC dONC }X-$Bܕl}OKA0+v؞}5h6d?R"H48dn< Q|vZmvvhhO΂{ s bwTb_<]1v Xሟ~(5*` -$-wr= #h7Wƞ38@y/Q rxP}q; _ct z ]W@$h֋>yc;UC|vJEdb}T&Bc?ftFe_'N]'034WXy@uhEW' n7[. gި#҅eR¬ﳑߎ<&8l%!p;{/IR G_KcD퇹ua G걎;n!`rqŦY͢vS|- Ha4qڬ^WhE됹񄰔( el9Z_ @ bE^9,펎}%C?lY>e={1 *%(b4yA,4t vYnV {vӠњ5XMӓsܻ7 %Jq K”16tx⟥%7x4(X]d"0>ƀsR~st0z %}DI.:fRPDp>k"l1tSCu.yK'W`SbN## IExY̱ӾpACa{xWU `kgGF;ՐX."Cc<  &$Ӵ)~QM3rDk00{4mۅ{6z1.XKg"U`5Vm.=5.hY o3 S6@"vk9rXTqwhvɌLYFbAٖ`AF3W72S25'9&fs 'S->1%.8s >^:lF؏dmpؓL+Adơ,!}6'gQ(VŪ(agٵC)51zczJ_5~`sq^R T>XD;ؘ6DGstl͙C;A0]3|PKt=Dl@c:b flot/NEWS.mdUT .US.USux [kor_ѐp P%%z}^;7EМim g3hS[WΩ! 69]]]uԃϞQ'ӫzl4zz87nḶ^o *7,>-ҖKՖɌsުoil[*S6M[xָF=Ξ_Kq{unkPwǺ2uzqQ(L7*UM̨EUc2(uٝȻ^xe͊[emijLݨM]mL   ̍TܚGϕkLqhgdjj>5r+.XN]Nu5Tt_'E_?C{Wm5.BٲD=L'::ejme5k{vjƼ{.Z:Ձ)uDn~T՚N7GUyǗfl~ꔉ' ;ѩQVmkM~Υ@d!Oָ} ̛,p8/|ZvfT!rf^U~umpbcgEK,Yے7 E:%|^A _ngWuuuT17+}oafKn~*X]mxqzuνo7 ɘuіT5#@p6;sk<hRތwRI|rJ!pxN2Os,PW[^U9EG[q|٦N7{Uy0O"۱3T%`TbsSWHwp>[C?0?ot;|~*k^$@KUme)F_2Kww>)U̝wF}mʫӀJ`5,fm $ӵ_޼;g,u\U8E8IlI#@49b0Q7xAyU~ǀA/bG|ff̪\K 0ɱEbP+׌_n xF5?7 S2 V=&s19Zgq H@N%[g 56Id <(SiZhm9,u\J^)NfѼ@әC.ajߡ?r i0y'C^Uz5Wlc8=*\Ď-ZOEN_o ě6K Uax+!H"AprxԖš,\7?'APքH<10 -q{L̮[2 #H],?]Z_NuYok=B{Dfs3ȶ<uI-ECMKU2V]in]fM 1g,:jF"16S+"7 =u&&'M 9+F8g$207-?W4! 0F S q&a9ޟI;|Îޯ~[O@x|D!@DJHn'9Jc= ߗI@"h C̣~X=e^,zՒc(SoP3wczomq8<_ ^;H*Q:>X2E`UfP7>oMb1awӫ\Bv#o ;M/K>#~;<5E?{H2hxaWk}zv|eκ,I>,ˉ6%%T{T7۹7fPm̠a rp>p$sx-m9^dXr+7E[_ p%;ޮf#C|]鍭Uf4ȅl *e s ڸsKʾ/}؋#SC@m!zT3f<C4rv<^$| jgBg$00/d TaoIm>̊sє^!xÏ"`lYyޡqwKXkG}H3`Ô(eB_6UpiNX=ZؾO}w9 ~q#t)Ё/lEUUA9=9dgP/xtF-F!/;[=2YZM:9kFY֤#D}w0eAlʷ9IDF|.k{|;5y'dUibI YmT)'@PL:G[D* )"QAEǸQm2: oV|5HD[?Of5T+siV 6FDMN=|0詧Sj&@Ոa ^~!%.ۙG35[TcϻK# l+^xsala}O %[o-jXAIԍ]ƲOjNsX ;Ml7f2.B`yTȼEslx|QM4KrP!zwcyf. 7gT\CD "7:87J n.0XDE95yj[DXm6$-=/C R5ik})>Vt;96uchKf`p21 jDKqKCo%+ eb= }ycȏ1O`* kv$ e)-~ouRV1]!ctJp0b#C3"}M>t)Ux A/_?~RP_-yTeA6J2pM{.4*vd+Aܛ0c^I':1^nﻏw%Rv :I ɇFB%ѐ.4$^fUP/ NFe'%LtĀ@܁T3lCzrەLqɓ~DC5 ;<S@aַY(xGP$$D SNb:viF58A۔$߳Ԯ%„z,7 5[˃=[JN7޲<`*oQ eSmhڠ3Fh>>K`]Ffur`3`wߊ?.(F9`M$q~L.V٬; FFdv/;ݫ/Z,h,lVzR lq ү%;Ý.\)|61RARo|j608`mI?H='A3`lU` Mt \y0{Lu7g}]O}_k@]]C9u-fa0D_xSS}ehn&$ZVG"S'O%M-㜔g n i dmmk8MĞ'0yF(ƽ*|yv=44i!X@ңH&l~;A 2ܦ $=H? s,3q|:u.} M@E>0ZA*G(裉/SǸjY|$#4ʪ9} r((Guo%Hq ?0QiUV 6 XU,z]R4!`M? H`l9lɳrk]DERH`bi]uWV|ɛ~'ZZxzdlo^8_4';ahsr4|)\8C>@ZrC;< 9QZB7#.:əV}Fu>]Eä ]&Asas8(+5:&&F0M!D~`R^ǃ=JU\|G} 1<$)ţ7I4{AB,sd0*=Yٻ9]!F־8\t"x(Dc),ɰlʣpJP 8..6+-g pGaOd'-^Ρsdcڭ)#,UtZ{ U0ŅQƎԇ*vMx waPjd&kx]]a(> &f d"?&E23\ .,w'f#"w)ﴻlg}6YGz^kKv' ϴM c#!]"VMyq;Wg!Ҽi-򳷏lGFºn[>_3V1!?np(Zfyk-򻄵ю%?8^vK&?l%- &B*!Q J,:3*P U烅LzؚäjHĄ01D%7ØDZ/NXSS mwy7CinEt 6Sٵ6m%,LEl؉ۙdw6 H)s d$Dq8}|maŪ-Q2.CnŦݾzN^$803h 0 o܉?0]'wiPΖ~_FwZH<"\5>/'CrI{ [`3 |0Fjee/ZDsZ/8ҏ?g_ϰyýDDPLBڔgG Sjy$^>݇IJdxjMcf.%9fF5qOϓTןuISuzM_:`2L6Z QDhfգlÍ A޳"ňDxceQ~S3'F Es5p2 DжmC/`$ovnGmOW0|(+y=t|@tلGETÃrkL GAeÐq<$i@Rv7v(k RT警F|9WeޥZ#\)Ԍ`5׼=~¿&1n\mΚݢr,ڦ +: $[}4r`_n|59/ng{ѼVB/˔sF f:Vv2|,22x;7pK$0i9p&g(5WlGPJ-d3)v9ΛQ )eh)h哛OFt}:]9N3:<xt\W-Ї?*Bd+>B9Ն<+;\-x~a\LE):Cr鱘$+ J.A ZL>ZV|N90*7\ɋbvicH+ӣzhff e$/Dq'0 4*`DjiwOR&͖̊Vd T ɥZWa-(@hӿ2hYsEZ[c Vt6{a!)uV46CY UJpcrudvy-OfʁI, rbD3 s2f'k岭d8_g6̋N B.:IZGk~͹rPl!T>QnPv9&NkpybYT~2_Ҡ}ÇΖ|+ZPBb'ߦv(t]mB0}9kU"_n%Xvl:y|f\jX.`xE6MxIh"M~#Ln?:B[ @iF+cl)0:2qڊGU~Xkx.U:X {Y c 肄e@&[|;$e4"YL_y4txVPJiok%y״۫vFcŶeUa_Cu`FfЮ Y#0WaXUbӾ A?tH }fYp~˥9^j&w, -c) y|Ћj.N%#U5\,~}z=+Nn]gĨb8ѕ*iYv!IRNFL-"r$#E X6_[Vb`%1GmɏQ|/ >i<JKm!o{z|V#2bcMi4Ke\BY6`LmjМ]D{5dU R m]>7V)bgثg&fh Β~Ƕ,$k|vqBG f7*{-vwn9 |D}=yT)Ϗgux<+ة£ڡR!yh׊"=X f/YۑlΙ<}+?.`]xN| T?7Қйw8J&N;5U%e:u/ ͦU$6OOQZ V< ɷe3}IXǺcsy/2@ݹ3߀xZe{AUa3@\A8bd6*^=N5{XWJ82gN[lzU0~~#--R08! rA}μ<$6Hu뷘clNqˎ0Y?d29if.+%PжSj;Mw5_$qFONgiDUUS B{{{g(~Պ"?&4VzS\UƧy NY@ubS. O?e;=]C5}1h;.eßo؁jscb/ 7 Av~QA,m> ;YBe9օ "RV%omzAsH;DI,آpU e$ _"{8Iq"Ai\s%]Ԁ* j3>sStr_4ͯ:!ZNuߑ&{ XD,N L9bƩ: ċLۍRNG'E@>:%vѕqRhY z5V|β-X]U+|Qャ7uJV:[Lp7ˌG)ViQǽ$-s?[Y yDx85 ~*$@ (iC2\@ӂLI~!sX;-Qy1܍G?:RpP=X1qX.(J0,w'P?@ge#@kic!Ր"$ AX\jZأTshgzBg]RB}Z:nmd^IW!f)tޫOrz VNT}R~%&<= #-dW EF_nz-\6QH3$o DOsT.K1KPD,P=*E:DLgT̔ gY(FYo!+kۑ <'rG˻d@ 5vb9qn@bIRD$oI N,&ĴTq7W%vuwx5Ǡԣ5E-@[%O(Ҷf }]GM1%NIeG2Ɖ*lnx("[.Hj8x pD}L@e<8+%tK'Jʤ7/Y|3dR힃ʛ;&kZψ1;ìƃUؼ{LA\SvZXzCG ߥ#[|Sܹ U:qn%>%!|RzS<&: ŷ0߿Foj~#gIEj*zKrFSE[ۍ _QRb;!rR*Bzڭ/[2_ۆ1B%[〄U[}Φ)HgI?,Ye VpEZM'X.JU(>4ul0 F"SZBF9[m5Û!lY6VF8!e5S^/ɁFb-O >'Q$ָ'P?+ZZW5i{V+uKNY'"k:נ|rmWܤnX߬%|ڻo0i#2鹴9*co^=+7DŽ ήѤNP'{Z{YU @C1`?uޑbH=Q^Ȅ#'OfD=ϗk_2bօ꼮c#m8]fE)0ϥL#(%Px3^Yb8k.M@_pWjx~6dZ7TfN{aOuI3iی+fADxX:>UuۋjsE GO0Y,|#e[be515fvk̋pdox2"ߥ 4z T "=ZK%)ݶU $14ƪ6Ai'e~YEHHYIOr+Hf4A54=X V&ۿzkgt^ppⷾ,zTIv%҈ K}(,wގ[kV [tSQz7fïfo^ 0_w(17̪CgaQ0Y1S{qԬgOWh.=\.1ֻ߰^P\͉x~YC 4h=>:&9\濬>z8n=b:&M>T~i U&E9nʫpqia6IMe&1f5p<+:!3"Dܣr$!x6&W]at_'+vZ5@H1]&+Yi x295jITdm}zbgq%8 ԔP*ZAL\œ~A@p#DFT'T2o'F3:Kk%ΩbVUvX=_#quY-,ߠf_MM;rT%)h&]QcߊR~JJ xr+eĴR7 G1ӿ{@-A.,+FXxdZVUӦ}Xyȯ7HniĬy\6,vv֐r:*@5`TUwk!邇T {*re&knmhuy5| =sͫ\&u ѿ}Lv3Fh?1 )kLPy?6ز:!t5yps>m:c涻XKJ_LHHĩ?Fɸh]vc[ i8?%A0[/:U8}I-\8A3wgn' 5)l$t/컰6 fZ;UӍC;qM=#YD=xPI?h$`3_>)e. `.G7-y=:?vU$|RŲu .ԍK#.RC}R5$ӦkClR1{~2ӡ3yQ=Et[(*Ћ`o7BLϹR^ZPKt=Dflot/PLUGINS.mdUT .US.USux X]6}篸 0U&8A(ɢih}X,J-PcKJb#6aGvvtuO4Rz!l&-5~6vdbw4"VfC1M-1;@d4 OUJW|fSuP>y̝R_~jÏ޻r#[`=z~Թjb&n]>72޼!%IsݰW{80 RcN0ԯ~}4$H%7uiAv5 [tc"p-hβ~%gGdн})N7A;z;u 9;4áS\*mc iN68`T,^N)LƷ&f}J="=, bR0ºD |Ʉ!}o@׏:6 VA7{t(q.^ͅ4f P`Y5*B#x_\PRJj8l#`I.zj:I6Sg.XR2ZH}(CoZyݚzH;R$岊&؜ܬjcNgIrRlwh$V f[;~0p =/{?:do~AM8[4༸(m?ekDҿ]J3g]u?QG#: HߜVǧKNr6.^Z1`_I^sӨw8o_Cd.lH̰XF.$!eH+9x^d,8#-=ϪϟNń<{[&By80!ҁou\|4!b;ol),?L֢U 8E]}"#BphI!q{0ѻGКD2|HDikl[[m9jcuW:C֔˧_h;#Ck fs-pzu%ì5aR/7,UbW@T@of0ab̠rYB%}(#br剸LN!W"8SMkc?:a>r:X^YEzc.[pbWؗd)AdP{r:)I ԦϧO.;Yhd#b!3eSIQ¥'>eP}fBf?:eFelfΞGu޴Q `*e!&ʖh q@Kdk+&z#ol`JD)>y^e8(0AY ~9 e b&)`(!ā`vЁ˴ϞL?bo6'{ N@3Zta<*.N8s\Hx\ 7ծe 9SOF%S}:k.%GGۍb vs$@&6;P34hH<;+uCIg"|+Jruc!ɊM!Aۅsv-9ZtXy]h^k u#/Q;FfkFOZvn HGx{e jz\" =#m e3xSCpA="B lhm5eC*Ք^Pl֤S x*.q%x )3/UBh3 bK,!5O͹]gƄim*׳dOJ8;" L@~joH=FcԚ~O+ᯃHMKEdhe0Q銭vZHCZ;#:x8z'Ձ=^όUzW5k߰ОB6ֱvN ^`%m)ZZRnBҪd ךj4 ~i3PR.۽+rOQԸ- A'H Zdmed˟4n#;teZ /DT`C--T!0>;)5IE #_[ VGzCn=?Lؓx B.<$pJqξs9Xj%&6,VCs0APBCr.Si妍uSdƒu `B붨<*'3nMR\zb ę "i š$Y]AᠶQjX/&NU( b(i^ u48T]9@@An_^U'=^%0"#%7G=:iTLl(YqT |'AbvtݸV!de6 x?dXOEz;:9݁ǥ!CQЅB36ڬy؄Dք__\7|utVwIF̚h04Z> ׹W8ܤX!?}ك=MEbR+I.ݻC5 > e-T<2'(\/kqDIRFǾV<窹VLhպ(mq@牐2<'0%~ar;-ꁫ]$ KVFCTiR\ 79?j cb3X3J`s]\ =^%zD֘k3>UzE_98'kKiQX UqT/yo`B*!NrNp爕wcR]. Z,g ܡ qݜ.7: fB ,aC0ކ^`yq ,:Vk|GAp{//V=+V婞Eɱ@dii91Ճ_A!ƎFl_L9(t}w7=VM 4Gp_/$Vx` E'c^mzP0`R`XuK?\8eU>Lt&,R';>EŻKrXB.|/rD N͇q@DHV2}=E$ PK +DAflot/UT&Sux PKt=D=kID ?flot/API.mdUT.USux PKt=D6-? Iflot/CONTRIBUTING.mdUT.USux PK t=DAOPflot/examples/UT.USux PKt=DC^<Pflot/examples/.DS_StoreUT.USux PK t=DAFUflot/examples/ajax/UT.USux PKt=D^BI,Uflot/examples/ajax/data-eu-gdp-growth-1.jsonUT.USux PKt=D;SOc,;Vflot/examples/ajax/data-eu-gdp-growth-2.jsonUT.USux PKt=D>[},Vflot/examples/ajax/data-eu-gdp-growth-3.jsonUT.USux PKt=DUd,Wflot/examples/ajax/data-eu-gdp-growth-4.jsonUT.USux PKt=Du։o,{Xflot/examples/ajax/data-eu-gdp-growth-5.jsonUT.USux PKt=Du։o*PYflot/examples/ajax/data-eu-gdp-growth.jsonUT.USux PKt=D zi-#Zflot/examples/ajax/data-japan-gdp-growth.jsonUT.USux PKt=Dhg+Zflot/examples/ajax/data-usa-gdp-growth.jsonUT.USux PKt=D5[flot/examples/ajax/index.htmlUT.USux PK t=DAcflot/examples/annotating/UT.USux PKt=DD= #Ycflot/examples/annotating/index.htmlUT.USux PK t=DAhflot/examples/axes-interacting/UT.USux PKt=D/1B )iflot/examples/axes-interacting/index.htmlUT.USux PK t=DAEnflot/examples/axes-multiple/UT.USux PKt=DɦXRc&nflot/examples/axes-multiple/index.htmlUT.USux PK t=DASflot/examples/axes-time/UT.USux PKt=D}OG"flot/examples/axes-time/index.htmlUT.USux PK t=DAߣflot/examples/axes-time-zones/UT.USux PKt=Dĥ}j+%7flot/examples/axes-time-zones/date.jsUT.USux PKt=D cz (flot/examples/axes-time-zones/index.htmlUT.USux PK t=D!Aflot/examples/axes-time-zones/tz/UT.USux PKt=D)flot/examples/axes-time-zones/tz/backwardUT.USux PKt=Dn )flot/examples/axes-time-zones/tz/etceteraUT.USux PKt=D}Uk%'}flot/examples/axes-time-zones/tz/europeUT.USux PKt=D0|(Iflot/examples/axes-time-zones/tz/factoryUT.USux PKt=D," ,ɸflot/examples/axes-time-zones/tz/iso3166.tabUT.USux PKt=DA`.r ,&flot/examples/axes-time-zones/tz/leapsecondsUT.USux PKt=D馺o-flot/examples/axes-time-zones/tz/northamericaUT.USux PKt=DH2'+uflot/examples/axes-time-zones/tz/pacificnewUT.USux PKt=D jK(xflot/examples/axes-time-zones/tz/solar87UT.USux PKt=Dggr |K(flot/examples/axes-time-zones/tz/solar88UT.USux PKt=DCmD L(yflot/examples/axes-time-zones/tz/solar89UT.USux PKt=D$o]"-flot/examples/axes-time-zones/tz/southamericaUT.USux PKt=D (Iflot/examples/axes-time-zones/tz/systemvUT.USux PKt=D 4.Yflot/examples/axes-time-zones/tz/yearistype.shUT.USux PKt=DVjP$M)flot/examples/axes-time-zones/tz/zone.tabUT.USux PK t=Dx MN'flot/examples/background.pngUT.USux PK t=DA(flot/examples/basic-options/UT.USux PKt=D&;)flot/examples/basic-options/index.htmlUT.USux PK t=DA-flot/examples/basic-usage/UT.USux PKt=DVy50$-flot/examples/basic-usage/index.htmlUT.USux PK t=DA1flot/examples/canvas/UT.USux PKt=DWX 2c1flot/examples/canvas/index.htmlUT.USux PK t=DABNflot/examples/categories/UT.USux PKt=D#Nflot/examples/categories/index.htmlUT.USux PKt=DQ:zQflot/examples/examples.cssUT.USux PK t=DATflot/examples/gauge/UT.USux PK t=DATflot/examples/image/UT.USux PKt=D٭JT.9Uflot/examples/image/hs-2004-27-a-large-web.jpgUT.USux PKt=Dܧbflot/examples/image/index.htmlUT.USux PKt=D`6 `flot/examples/index.htmlUT.USux PK t=DAflot/examples/interacting/UT.USux PKt=Dނ_5 $flot/examples/interacting/index.htmlUT.USux PK t=DA{flot/examples/navigate/UT.USux PK t=D:%flot/examples/navigate/arrow-down.gifUT.USux PK t=Dܽh{{%flot/examples/navigate/arrow-left.gifUT.USux PK t=D1q&flot/examples/navigate/arrow-right.gifUT.USux PK t=D} #zflot/examples/navigate/arrow-up.gifUT.USux PKt=DoEBk!kflot/examples/navigate/index.htmlUT.USux PK t=DAflot/examples/percentiles/UT.USux PKt=D]D 5$\flot/examples/percentiles/index.htmlUT.USux PK t=DA flot/examples/realtime/UT.USux PKt=D4  !O flot/examples/realtime/index.htmlUT.USux PK t=DAflot/examples/resize/UT.USux PKt=DҲ: flot/examples/resize/index.htmlUT.USux PK t=DA{flot/examples/selection/UT.USux PKt=D04"flot/examples/selection/index.htmlUT.USux PK t=DA]flot/examples/series-errorbars/UT.USux PKt=D̓' )flot/examples/series-errorbars/index.htmlUT.USux PK t=DA@%flot/examples/series-pie/UT.USux PKt=DT4ao#%flot/examples/series-pie/index.htmlUT.USux PK t=DAAflot/examples/series-toggle/UT.USux PKt=D@x&Aflot/examples/series-toggle/index.htmlUT.USux PK t=DAJflot/examples/series-types/UT.USux PKt=DĀ S%lJflot/examples/series-types/index.htmlUT.USux PK t=DANflot/examples/shared/UT.USux PK t=DAmNflot/examples/shared/jquery-ui/UT.USux PKt=D̝ۛ0Nflot/examples/shared/jquery-ui/jquery-ui.min.cssUT.USux PKt=DR#x/Qflot/examples/shared/jquery-ui/jquery-ui.min.jsUT.USux PK t=DAvflot/examples/stacking/UT.USux PKt=D5B%o !_vflot/examples/stacking/index.htmlUT.USux PK t=DAzflot/examples/symbols/UT.USux PKt=DMDpe$ /{flot/examples/symbols/index.htmlUT.USux PK t=DACflot/examples/threshold/UT.USux PKt=D^W"flot/examples/threshold/index.htmlUT.USux PK t=DAflot/examples/tracking/UT.USux PKt=D& !flot/examples/tracking/index.htmlUT.USux PK t=DAflot/examples/visitors/UT.USux PKt=D>d[!5flot/examples/visitors/index.htmlUT.USux PK t=DAflot/examples/zooming/UT.USux PKt=Dx+d Dflot/examples/zooming/index.htmlUT.USux PKt=D/p0ףflot/excanvas.jsUT.USux PKt=D:@qyrKflot/excanvas.min.jsUT.USux PKt=DC flot/FAQ.mdUT.USux PKt=D0flot/jquery.colorhelpers.jsUT.USux PKt=D)= !flot/jquery.colorhelpers.min.jsUT.USux PKt=De= %flot/jquery.flot.canvas.jsUT.USux PK@Dtff|qflot/jquery.flot.canvas.min.jsUT2USux PKt=Du>ifflot/jquery.flot.categories.jsUT.USux PK @DR& "mflot/jquery.flot.categories.min.jsUT2USux PKt=D%{+flot/jquery.flot.crosshair.jsUT.USux PK(@DV|-r!!flot/jquery.flot.crosshair.min.jsUT2USux PKt=Dkj F1=%flot/jquery.flot.errorbars.jsUT.USux PK1@D<M!f2flot/jquery.flot.errorbars.min.jsUT2USux PKt=D^1T9flot/jquery.flot.fillbetween.jsUT.USux PK:@D9Bq #@flot/jquery.flot.fillbetween.min.jsUT2USux PKt=D 8 Dflot/jquery.flot.image.jsUT.USux PKD@Ds9 M{ Nflot/jquery.flot.image.min.jsUT2USux PKt=Dd(vj[Rflot/jquery.flot.jsUT.USux PK @D_8flot/jquery.flot.min.jsUT2USux PKt=D:׍7flot/jquery.flot.navigate.jsUT.USux PKM@Dľ  flot/jquery.flot.navigate.min.jsUT3USux PKt=Db%x]oflot/jquery.flot.pie.jsUT.USux PKU@D"X /g.flot/jquery.flot.pie.min.jsUT3USux PKt=D!D"y <flot/jquery.flot.resize.jsUT.USux PK]@DaQ( }Bflot/jquery.flot.resize.min.jsUT"3USux PKt=DY_U3Fflot/jquery.flot.selection.jsUT.USux PKg@DS!Uflot/jquery.flot.selection.min.jsUT23USux PKt=D`X&\flot/jquery.flot.stack.jsUT.USux PKo@DCƚ dflot/jquery.flot.stack.min.jsUTB3USux PKt=DWN hflot/jquery.flot.symbol.jsUT.USux PKz@D(lflot/jquery.flot.symbol.min.jsUTX3USux PKt=D-)Knflot/jquery.flot.threshold.jsUT.USux PK@DgW0!Ptflot/jquery.flot.threshold.min.jsUTh3USux PKt=D%1`-wflot/jquery.flot.time.jsUT.USux PK@D( Fflot/jquery.flot.time.min.jsUT|3USux PKt=D+5Iflot/jquery.jsUT.USux PKt=DZO`m+flot/jquery.min.jsUT.USux PKt=DAΈ|-d flot/LICENSE.txtUT.USux PKt=Dd؂ xg flot/MakefileUT.USux PKt=Dl@c:b h flot/NEWS.mdUT.USux PKt=D flot/PLUGINS.mdUT.USux PKt=DTê flot/README.mdUT.USux PKD8_ criterion-1.1.0.0/js-src/jquery-2.1.1.js0000644000000000000000000074306712505102676015573 0ustar0000000000000000/*! * jQuery JavaScript Library v2.1.1 * http://jquery.com/ * * Includes Sizzle.js * http://sizzlejs.com/ * * Copyright 2005, 2014 jQuery Foundation, Inc. and other contributors * Released under the MIT license * http://jquery.org/license * * Date: 2014-05-01T17:11Z */ (function( global, factory ) { if ( typeof module === "object" && typeof module.exports === "object" ) { // For CommonJS and CommonJS-like environments where a proper window is present, // execute the factory and get jQuery // For environments that do not inherently posses a window with a document // (such as Node.js), expose a jQuery-making factory as module.exports // This accentuates the need for the creation of a real window // e.g. var jQuery = require("jquery")(window); // See ticket #14549 for more info module.exports = global.document ? factory( global, true ) : function( w ) { if ( !w.document ) { throw new Error( "jQuery requires a window with a document" ); } return factory( w ); }; } else { factory( global ); } // Pass this if window is not defined yet }(typeof window !== "undefined" ? window : this, function( window, noGlobal ) { // Can't do this because several apps including ASP.NET trace // the stack via arguments.caller.callee and Firefox dies if // you try to trace through "use strict" call chains. (#13335) // Support: Firefox 18+ // var arr = []; var slice = arr.slice; var concat = arr.concat; var push = arr.push; var indexOf = arr.indexOf; var class2type = {}; var toString = class2type.toString; var hasOwn = class2type.hasOwnProperty; var support = {}; var // Use the correct document accordingly with window argument (sandbox) document = window.document, version = "2.1.1", // Define a local copy of jQuery jQuery = function( selector, context ) { // The jQuery object is actually just the init constructor 'enhanced' // Need init if jQuery is called (just allow error to be thrown if not included) return new jQuery.fn.init( selector, context ); }, // Support: Android<4.1 // Make sure we trim BOM and NBSP rtrim = /^[\s\uFEFF\xA0]+|[\s\uFEFF\xA0]+$/g, // Matches dashed string for camelizing rmsPrefix = /^-ms-/, rdashAlpha = /-([\da-z])/gi, // Used by jQuery.camelCase as callback to replace() fcamelCase = function( all, letter ) { return letter.toUpperCase(); }; jQuery.fn = jQuery.prototype = { // The current version of jQuery being used jquery: version, constructor: jQuery, // Start with an empty selector selector: "", // The default length of a jQuery object is 0 length: 0, toArray: function() { return slice.call( this ); }, // Get the Nth element in the matched element set OR // Get the whole matched element set as a clean array get: function( num ) { return num != null ? // Return just the one element from the set ( num < 0 ? this[ num + this.length ] : this[ num ] ) : // Return all the elements in a clean array slice.call( this ); }, // Take an array of elements and push it onto the stack // (returning the new matched element set) pushStack: function( elems ) { // Build a new jQuery matched element set var ret = jQuery.merge( this.constructor(), elems ); // Add the old object onto the stack (as a reference) ret.prevObject = this; ret.context = this.context; // Return the newly-formed element set return ret; }, // Execute a callback for every element in the matched set. // (You can seed the arguments with an array of args, but this is // only used internally.) each: function( callback, args ) { return jQuery.each( this, callback, args ); }, map: function( callback ) { return this.pushStack( jQuery.map(this, function( elem, i ) { return callback.call( elem, i, elem ); })); }, slice: function() { return this.pushStack( slice.apply( this, arguments ) ); }, first: function() { return this.eq( 0 ); }, last: function() { return this.eq( -1 ); }, eq: function( i ) { var len = this.length, j = +i + ( i < 0 ? len : 0 ); return this.pushStack( j >= 0 && j < len ? [ this[j] ] : [] ); }, end: function() { return this.prevObject || this.constructor(null); }, // For internal use only. // Behaves like an Array's method, not like a jQuery method. push: push, sort: arr.sort, splice: arr.splice }; jQuery.extend = jQuery.fn.extend = function() { var options, name, src, copy, copyIsArray, clone, target = arguments[0] || {}, i = 1, length = arguments.length, deep = false; // Handle a deep copy situation if ( typeof target === "boolean" ) { deep = target; // skip the boolean and the target target = arguments[ i ] || {}; i++; } // Handle case when target is a string or something (possible in deep copy) if ( typeof target !== "object" && !jQuery.isFunction(target) ) { target = {}; } // extend jQuery itself if only one argument is passed if ( i === length ) { target = this; i--; } for ( ; i < length; i++ ) { // Only deal with non-null/undefined values if ( (options = arguments[ i ]) != null ) { // Extend the base object for ( name in options ) { src = target[ name ]; copy = options[ name ]; // Prevent never-ending loop if ( target === copy ) { continue; } // Recurse if we're merging plain objects or arrays if ( deep && copy && ( jQuery.isPlainObject(copy) || (copyIsArray = jQuery.isArray(copy)) ) ) { if ( copyIsArray ) { copyIsArray = false; clone = src && jQuery.isArray(src) ? src : []; } else { clone = src && jQuery.isPlainObject(src) ? src : {}; } // Never move original objects, clone them target[ name ] = jQuery.extend( deep, clone, copy ); // Don't bring in undefined values } else if ( copy !== undefined ) { target[ name ] = copy; } } } } // Return the modified object return target; }; jQuery.extend({ // Unique for each copy of jQuery on the page expando: "jQuery" + ( version + Math.random() ).replace( /\D/g, "" ), // Assume jQuery is ready without the ready module isReady: true, error: function( msg ) { throw new Error( msg ); }, noop: function() {}, // See test/unit/core.js for details concerning isFunction. // Since version 1.3, DOM methods and functions like alert // aren't supported. They return false on IE (#2968). isFunction: function( obj ) { return jQuery.type(obj) === "function"; }, isArray: Array.isArray, isWindow: function( obj ) { return obj != null && obj === obj.window; }, isNumeric: function( obj ) { // parseFloat NaNs numeric-cast false positives (null|true|false|"") // ...but misinterprets leading-number strings, particularly hex literals ("0x...") // subtraction forces infinities to NaN return !jQuery.isArray( obj ) && obj - parseFloat( obj ) >= 0; }, isPlainObject: function( obj ) { // Not plain objects: // - Any object or value whose internal [[Class]] property is not "[object Object]" // - DOM nodes // - window if ( jQuery.type( obj ) !== "object" || obj.nodeType || jQuery.isWindow( obj ) ) { return false; } if ( obj.constructor && !hasOwn.call( obj.constructor.prototype, "isPrototypeOf" ) ) { return false; } // If the function hasn't returned already, we're confident that // |obj| is a plain object, created by {} or constructed with new Object return true; }, isEmptyObject: function( obj ) { var name; for ( name in obj ) { return false; } return true; }, type: function( obj ) { if ( obj == null ) { return obj + ""; } // Support: Android < 4.0, iOS < 6 (functionish RegExp) return typeof obj === "object" || typeof obj === "function" ? class2type[ toString.call(obj) ] || "object" : typeof obj; }, // Evaluates a script in a global context globalEval: function( code ) { var script, indirect = eval; code = jQuery.trim( code ); if ( code ) { // If the code includes a valid, prologue position // strict mode pragma, execute code by injecting a // script tag into the document. if ( code.indexOf("use strict") === 1 ) { script = document.createElement("script"); script.text = code; document.head.appendChild( script ).parentNode.removeChild( script ); } else { // Otherwise, avoid the DOM node creation, insertion // and removal by using an indirect global eval indirect( code ); } } }, // Convert dashed to camelCase; used by the css and data modules // Microsoft forgot to hump their vendor prefix (#9572) camelCase: function( string ) { return string.replace( rmsPrefix, "ms-" ).replace( rdashAlpha, fcamelCase ); }, nodeName: function( elem, name ) { return elem.nodeName && elem.nodeName.toLowerCase() === name.toLowerCase(); }, // args is for internal usage only each: function( obj, callback, args ) { var value, i = 0, length = obj.length, isArray = isArraylike( obj ); if ( args ) { if ( isArray ) { for ( ; i < length; i++ ) { value = callback.apply( obj[ i ], args ); if ( value === false ) { break; } } } else { for ( i in obj ) { value = callback.apply( obj[ i ], args ); if ( value === false ) { break; } } } // A special, fast, case for the most common use of each } else { if ( isArray ) { for ( ; i < length; i++ ) { value = callback.call( obj[ i ], i, obj[ i ] ); if ( value === false ) { break; } } } else { for ( i in obj ) { value = callback.call( obj[ i ], i, obj[ i ] ); if ( value === false ) { break; } } } } return obj; }, // Support: Android<4.1 trim: function( text ) { return text == null ? "" : ( text + "" ).replace( rtrim, "" ); }, // results is for internal usage only makeArray: function( arr, results ) { var ret = results || []; if ( arr != null ) { if ( isArraylike( Object(arr) ) ) { jQuery.merge( ret, typeof arr === "string" ? [ arr ] : arr ); } else { push.call( ret, arr ); } } return ret; }, inArray: function( elem, arr, i ) { return arr == null ? -1 : indexOf.call( arr, elem, i ); }, merge: function( first, second ) { var len = +second.length, j = 0, i = first.length; for ( ; j < len; j++ ) { first[ i++ ] = second[ j ]; } first.length = i; return first; }, grep: function( elems, callback, invert ) { var callbackInverse, matches = [], i = 0, length = elems.length, callbackExpect = !invert; // Go through the array, only saving the items // that pass the validator function for ( ; i < length; i++ ) { callbackInverse = !callback( elems[ i ], i ); if ( callbackInverse !== callbackExpect ) { matches.push( elems[ i ] ); } } return matches; }, // arg is for internal usage only map: function( elems, callback, arg ) { var value, i = 0, length = elems.length, isArray = isArraylike( elems ), ret = []; // Go through the array, translating each of the items to their new values if ( isArray ) { for ( ; i < length; i++ ) { value = callback( elems[ i ], i, arg ); if ( value != null ) { ret.push( value ); } } // Go through every key on the object, } else { for ( i in elems ) { value = callback( elems[ i ], i, arg ); if ( value != null ) { ret.push( value ); } } } // Flatten any nested arrays return concat.apply( [], ret ); }, // A global GUID counter for objects guid: 1, // Bind a function to a context, optionally partially applying any // arguments. proxy: function( fn, context ) { var tmp, args, proxy; if ( typeof context === "string" ) { tmp = fn[ context ]; context = fn; fn = tmp; } // Quick check to determine if target is callable, in the spec // this throws a TypeError, but we will just return undefined. if ( !jQuery.isFunction( fn ) ) { return undefined; } // Simulated bind args = slice.call( arguments, 2 ); proxy = function() { return fn.apply( context || this, args.concat( slice.call( arguments ) ) ); }; // Set the guid of unique handler to the same of original handler, so it can be removed proxy.guid = fn.guid = fn.guid || jQuery.guid++; return proxy; }, now: Date.now, // jQuery.support is not used in Core but other projects attach their // properties to it so it needs to exist. support: support }); // Populate the class2type map jQuery.each("Boolean Number String Function Array Date RegExp Object Error".split(" "), function(i, name) { class2type[ "[object " + name + "]" ] = name.toLowerCase(); }); function isArraylike( obj ) { var length = obj.length, type = jQuery.type( obj ); if ( type === "function" || jQuery.isWindow( obj ) ) { return false; } if ( obj.nodeType === 1 && length ) { return true; } return type === "array" || length === 0 || typeof length === "number" && length > 0 && ( length - 1 ) in obj; } var Sizzle = /*! * Sizzle CSS Selector Engine v1.10.19 * http://sizzlejs.com/ * * Copyright 2013 jQuery Foundation, Inc. and other contributors * Released under the MIT license * http://jquery.org/license * * Date: 2014-04-18 */ (function( window ) { var i, support, Expr, getText, isXML, tokenize, compile, select, outermostContext, sortInput, hasDuplicate, // Local document vars setDocument, document, docElem, documentIsHTML, rbuggyQSA, rbuggyMatches, matches, contains, // Instance-specific data expando = "sizzle" + -(new Date()), preferredDoc = window.document, dirruns = 0, done = 0, classCache = createCache(), tokenCache = createCache(), compilerCache = createCache(), sortOrder = function( a, b ) { if ( a === b ) { hasDuplicate = true; } return 0; }, // General-purpose constants strundefined = typeof undefined, MAX_NEGATIVE = 1 << 31, // Instance methods hasOwn = ({}).hasOwnProperty, arr = [], pop = arr.pop, push_native = arr.push, push = arr.push, slice = arr.slice, // Use a stripped-down indexOf if we can't use a native one indexOf = arr.indexOf || function( elem ) { var i = 0, len = this.length; for ( ; i < len; i++ ) { if ( this[i] === elem ) { return i; } } return -1; }, booleans = "checked|selected|async|autofocus|autoplay|controls|defer|disabled|hidden|ismap|loop|multiple|open|readonly|required|scoped", // Regular expressions // Whitespace characters http://www.w3.org/TR/css3-selectors/#whitespace whitespace = "[\\x20\\t\\r\\n\\f]", // http://www.w3.org/TR/css3-syntax/#characters characterEncoding = "(?:\\\\.|[\\w-]|[^\\x00-\\xa0])+", // Loosely modeled on CSS identifier characters // An unquoted value should be a CSS identifier http://www.w3.org/TR/css3-selectors/#attribute-selectors // Proper syntax: http://www.w3.org/TR/CSS21/syndata.html#value-def-identifier identifier = characterEncoding.replace( "w", "w#" ), // Attribute selectors: http://www.w3.org/TR/selectors/#attribute-selectors attributes = "\\[" + whitespace + "*(" + characterEncoding + ")(?:" + whitespace + // Operator (capture 2) "*([*^$|!~]?=)" + whitespace + // "Attribute values must be CSS identifiers [capture 5] or strings [capture 3 or capture 4]" "*(?:'((?:\\\\.|[^\\\\'])*)'|\"((?:\\\\.|[^\\\\\"])*)\"|(" + identifier + "))|)" + whitespace + "*\\]", pseudos = ":(" + characterEncoding + ")(?:\\((" + // To reduce the number of selectors needing tokenize in the preFilter, prefer arguments: // 1. quoted (capture 3; capture 4 or capture 5) "('((?:\\\\.|[^\\\\'])*)'|\"((?:\\\\.|[^\\\\\"])*)\")|" + // 2. simple (capture 6) "((?:\\\\.|[^\\\\()[\\]]|" + attributes + ")*)|" + // 3. anything else (capture 2) ".*" + ")\\)|)", // Leading and non-escaped trailing whitespace, capturing some non-whitespace characters preceding the latter rtrim = new RegExp( "^" + whitespace + "+|((?:^|[^\\\\])(?:\\\\.)*)" + whitespace + "+$", "g" ), rcomma = new RegExp( "^" + whitespace + "*," + whitespace + "*" ), rcombinators = new RegExp( "^" + whitespace + "*([>+~]|" + whitespace + ")" + whitespace + "*" ), rattributeQuotes = new RegExp( "=" + whitespace + "*([^\\]'\"]*?)" + whitespace + "*\\]", "g" ), rpseudo = new RegExp( pseudos ), ridentifier = new RegExp( "^" + identifier + "$" ), matchExpr = { "ID": new RegExp( "^#(" + characterEncoding + ")" ), "CLASS": new RegExp( "^\\.(" + characterEncoding + ")" ), "TAG": new RegExp( "^(" + characterEncoding.replace( "w", "w*" ) + ")" ), "ATTR": new RegExp( "^" + attributes ), "PSEUDO": new RegExp( "^" + pseudos ), "CHILD": new RegExp( "^:(only|first|last|nth|nth-last)-(child|of-type)(?:\\(" + whitespace + "*(even|odd|(([+-]|)(\\d*)n|)" + whitespace + "*(?:([+-]|)" + whitespace + "*(\\d+)|))" + whitespace + "*\\)|)", "i" ), "bool": new RegExp( "^(?:" + booleans + ")$", "i" ), // For use in libraries implementing .is() // We use this for POS matching in `select` "needsContext": new RegExp( "^" + whitespace + "*[>+~]|:(even|odd|eq|gt|lt|nth|first|last)(?:\\(" + whitespace + "*((?:-\\d)?\\d*)" + whitespace + "*\\)|)(?=[^-]|$)", "i" ) }, rinputs = /^(?:input|select|textarea|button)$/i, rheader = /^h\d$/i, rnative = /^[^{]+\{\s*\[native \w/, // Easily-parseable/retrievable ID or TAG or CLASS selectors rquickExpr = /^(?:#([\w-]+)|(\w+)|\.([\w-]+))$/, rsibling = /[+~]/, rescape = /'|\\/g, // CSS escapes http://www.w3.org/TR/CSS21/syndata.html#escaped-characters runescape = new RegExp( "\\\\([\\da-f]{1,6}" + whitespace + "?|(" + whitespace + ")|.)", "ig" ), funescape = function( _, escaped, escapedWhitespace ) { var high = "0x" + escaped - 0x10000; // NaN means non-codepoint // Support: Firefox<24 // Workaround erroneous numeric interpretation of +"0x" return high !== high || escapedWhitespace ? escaped : high < 0 ? // BMP codepoint String.fromCharCode( high + 0x10000 ) : // Supplemental Plane codepoint (surrogate pair) String.fromCharCode( high >> 10 | 0xD800, high & 0x3FF | 0xDC00 ); }; // Optimize for push.apply( _, NodeList ) try { push.apply( (arr = slice.call( preferredDoc.childNodes )), preferredDoc.childNodes ); // Support: Android<4.0 // Detect silently failing push.apply arr[ preferredDoc.childNodes.length ].nodeType; } catch ( e ) { push = { apply: arr.length ? // Leverage slice if possible function( target, els ) { push_native.apply( target, slice.call(els) ); } : // Support: IE<9 // Otherwise append directly function( target, els ) { var j = target.length, i = 0; // Can't trust NodeList.length while ( (target[j++] = els[i++]) ) {} target.length = j - 1; } }; } function Sizzle( selector, context, results, seed ) { var match, elem, m, nodeType, // QSA vars i, groups, old, nid, newContext, newSelector; if ( ( context ? context.ownerDocument || context : preferredDoc ) !== document ) { setDocument( context ); } context = context || document; results = results || []; if ( !selector || typeof selector !== "string" ) { return results; } if ( (nodeType = context.nodeType) !== 1 && nodeType !== 9 ) { return []; } if ( documentIsHTML && !seed ) { // Shortcuts if ( (match = rquickExpr.exec( selector )) ) { // Speed-up: Sizzle("#ID") if ( (m = match[1]) ) { if ( nodeType === 9 ) { elem = context.getElementById( m ); // Check parentNode to catch when Blackberry 4.6 returns // nodes that are no longer in the document (jQuery #6963) if ( elem && elem.parentNode ) { // Handle the case where IE, Opera, and Webkit return items // by name instead of ID if ( elem.id === m ) { results.push( elem ); return results; } } else { return results; } } else { // Context is not a document if ( context.ownerDocument && (elem = context.ownerDocument.getElementById( m )) && contains( context, elem ) && elem.id === m ) { results.push( elem ); return results; } } // Speed-up: Sizzle("TAG") } else if ( match[2] ) { push.apply( results, context.getElementsByTagName( selector ) ); return results; // Speed-up: Sizzle(".CLASS") } else if ( (m = match[3]) && support.getElementsByClassName && context.getElementsByClassName ) { push.apply( results, context.getElementsByClassName( m ) ); return results; } } // QSA path if ( support.qsa && (!rbuggyQSA || !rbuggyQSA.test( selector )) ) { nid = old = expando; newContext = context; newSelector = nodeType === 9 && selector; // qSA works strangely on Element-rooted queries // We can work around this by specifying an extra ID on the root // and working up from there (Thanks to Andrew Dupont for the technique) // IE 8 doesn't work on object elements if ( nodeType === 1 && context.nodeName.toLowerCase() !== "object" ) { groups = tokenize( selector ); if ( (old = context.getAttribute("id")) ) { nid = old.replace( rescape, "\\$&" ); } else { context.setAttribute( "id", nid ); } nid = "[id='" + nid + "'] "; i = groups.length; while ( i-- ) { groups[i] = nid + toSelector( groups[i] ); } newContext = rsibling.test( selector ) && testContext( context.parentNode ) || context; newSelector = groups.join(","); } if ( newSelector ) { try { push.apply( results, newContext.querySelectorAll( newSelector ) ); return results; } catch(qsaError) { } finally { if ( !old ) { context.removeAttribute("id"); } } } } } // All others return select( selector.replace( rtrim, "$1" ), context, results, seed ); } /** * Create key-value caches of limited size * @returns {Function(string, Object)} Returns the Object data after storing it on itself with * property name the (space-suffixed) string and (if the cache is larger than Expr.cacheLength) * deleting the oldest entry */ function createCache() { var keys = []; function cache( key, value ) { // Use (key + " ") to avoid collision with native prototype properties (see Issue #157) if ( keys.push( key + " " ) > Expr.cacheLength ) { // Only keep the most recent entries delete cache[ keys.shift() ]; } return (cache[ key + " " ] = value); } return cache; } /** * Mark a function for special use by Sizzle * @param {Function} fn The function to mark */ function markFunction( fn ) { fn[ expando ] = true; return fn; } /** * Support testing using an element * @param {Function} fn Passed the created div and expects a boolean result */ function assert( fn ) { var div = document.createElement("div"); try { return !!fn( div ); } catch (e) { return false; } finally { // Remove from its parent by default if ( div.parentNode ) { div.parentNode.removeChild( div ); } // release memory in IE div = null; } } /** * Adds the same handler for all of the specified attrs * @param {String} attrs Pipe-separated list of attributes * @param {Function} handler The method that will be applied */ function addHandle( attrs, handler ) { var arr = attrs.split("|"), i = attrs.length; while ( i-- ) { Expr.attrHandle[ arr[i] ] = handler; } } /** * Checks document order of two siblings * @param {Element} a * @param {Element} b * @returns {Number} Returns less than 0 if a precedes b, greater than 0 if a follows b */ function siblingCheck( a, b ) { var cur = b && a, diff = cur && a.nodeType === 1 && b.nodeType === 1 && ( ~b.sourceIndex || MAX_NEGATIVE ) - ( ~a.sourceIndex || MAX_NEGATIVE ); // Use IE sourceIndex if available on both nodes if ( diff ) { return diff; } // Check if b follows a if ( cur ) { while ( (cur = cur.nextSibling) ) { if ( cur === b ) { return -1; } } } return a ? 1 : -1; } /** * Returns a function to use in pseudos for input types * @param {String} type */ function createInputPseudo( type ) { return function( elem ) { var name = elem.nodeName.toLowerCase(); return name === "input" && elem.type === type; }; } /** * Returns a function to use in pseudos for buttons * @param {String} type */ function createButtonPseudo( type ) { return function( elem ) { var name = elem.nodeName.toLowerCase(); return (name === "input" || name === "button") && elem.type === type; }; } /** * Returns a function to use in pseudos for positionals * @param {Function} fn */ function createPositionalPseudo( fn ) { return markFunction(function( argument ) { argument = +argument; return markFunction(function( seed, matches ) { var j, matchIndexes = fn( [], seed.length, argument ), i = matchIndexes.length; // Match elements found at the specified indexes while ( i-- ) { if ( seed[ (j = matchIndexes[i]) ] ) { seed[j] = !(matches[j] = seed[j]); } } }); }); } /** * Checks a node for validity as a Sizzle context * @param {Element|Object=} context * @returns {Element|Object|Boolean} The input node if acceptable, otherwise a falsy value */ function testContext( context ) { return context && typeof context.getElementsByTagName !== strundefined && context; } // Expose support vars for convenience support = Sizzle.support = {}; /** * Detects XML nodes * @param {Element|Object} elem An element or a document * @returns {Boolean} True iff elem is a non-HTML XML node */ isXML = Sizzle.isXML = function( elem ) { // documentElement is verified for cases where it doesn't yet exist // (such as loading iframes in IE - #4833) var documentElement = elem && (elem.ownerDocument || elem).documentElement; return documentElement ? documentElement.nodeName !== "HTML" : false; }; /** * Sets document-related variables once based on the current document * @param {Element|Object} [doc] An element or document object to use to set the document * @returns {Object} Returns the current document */ setDocument = Sizzle.setDocument = function( node ) { var hasCompare, doc = node ? node.ownerDocument || node : preferredDoc, parent = doc.defaultView; // If no document and documentElement is available, return if ( doc === document || doc.nodeType !== 9 || !doc.documentElement ) { return document; } // Set our document document = doc; docElem = doc.documentElement; // Support tests documentIsHTML = !isXML( doc ); // Support: IE>8 // If iframe document is assigned to "document" variable and if iframe has been reloaded, // IE will throw "permission denied" error when accessing "document" variable, see jQuery #13936 // IE6-8 do not support the defaultView property so parent will be undefined if ( parent && parent !== parent.top ) { // IE11 does not have attachEvent, so all must suffer if ( parent.addEventListener ) { parent.addEventListener( "unload", function() { setDocument(); }, false ); } else if ( parent.attachEvent ) { parent.attachEvent( "onunload", function() { setDocument(); }); } } /* Attributes ---------------------------------------------------------------------- */ // Support: IE<8 // Verify that getAttribute really returns attributes and not properties (excepting IE8 booleans) support.attributes = assert(function( div ) { div.className = "i"; return !div.getAttribute("className"); }); /* getElement(s)By* ---------------------------------------------------------------------- */ // Check if getElementsByTagName("*") returns only elements support.getElementsByTagName = assert(function( div ) { div.appendChild( doc.createComment("") ); return !div.getElementsByTagName("*").length; }); // Check if getElementsByClassName can be trusted support.getElementsByClassName = rnative.test( doc.getElementsByClassName ) && assert(function( div ) { div.innerHTML = "

"; // Support: Safari<4 // Catch class over-caching div.firstChild.className = "i"; // Support: Opera<10 // Catch gEBCN failure to find non-leading classes return div.getElementsByClassName("i").length === 2; }); // Support: IE<10 // Check if getElementById returns elements by name // The broken getElementById methods don't pick up programatically-set names, // so use a roundabout getElementsByName test support.getById = assert(function( div ) { docElem.appendChild( div ).id = expando; return !doc.getElementsByName || !doc.getElementsByName( expando ).length; }); // ID find and filter if ( support.getById ) { Expr.find["ID"] = function( id, context ) { if ( typeof context.getElementById !== strundefined && documentIsHTML ) { var m = context.getElementById( id ); // Check parentNode to catch when Blackberry 4.6 returns // nodes that are no longer in the document #6963 return m && m.parentNode ? [ m ] : []; } }; Expr.filter["ID"] = function( id ) { var attrId = id.replace( runescape, funescape ); return function( elem ) { return elem.getAttribute("id") === attrId; }; }; } else { // Support: IE6/7 // getElementById is not reliable as a find shortcut delete Expr.find["ID"]; Expr.filter["ID"] = function( id ) { var attrId = id.replace( runescape, funescape ); return function( elem ) { var node = typeof elem.getAttributeNode !== strundefined && elem.getAttributeNode("id"); return node && node.value === attrId; }; }; } // Tag Expr.find["TAG"] = support.getElementsByTagName ? function( tag, context ) { if ( typeof context.getElementsByTagName !== strundefined ) { return context.getElementsByTagName( tag ); } } : function( tag, context ) { var elem, tmp = [], i = 0, results = context.getElementsByTagName( tag ); // Filter out possible comments if ( tag === "*" ) { while ( (elem = results[i++]) ) { if ( elem.nodeType === 1 ) { tmp.push( elem ); } } return tmp; } return results; }; // Class Expr.find["CLASS"] = support.getElementsByClassName && function( className, context ) { if ( typeof context.getElementsByClassName !== strundefined && documentIsHTML ) { return context.getElementsByClassName( className ); } }; /* QSA/matchesSelector ---------------------------------------------------------------------- */ // QSA and matchesSelector support // matchesSelector(:active) reports false when true (IE9/Opera 11.5) rbuggyMatches = []; // qSa(:focus) reports false when true (Chrome 21) // We allow this because of a bug in IE8/9 that throws an error // whenever `document.activeElement` is accessed on an iframe // So, we allow :focus to pass through QSA all the time to avoid the IE error // See http://bugs.jquery.com/ticket/13378 rbuggyQSA = []; if ( (support.qsa = rnative.test( doc.querySelectorAll )) ) { // Build QSA regex // Regex strategy adopted from Diego Perini assert(function( div ) { // Select is set to empty string on purpose // This is to test IE's treatment of not explicitly // setting a boolean content attribute, // since its presence should be enough // http://bugs.jquery.com/ticket/12359 div.innerHTML = ""; // Support: IE8, Opera 11-12.16 // Nothing should be selected when empty strings follow ^= or $= or *= // The test attribute must be unknown in Opera but "safe" for WinRT // http://msdn.microsoft.com/en-us/library/ie/hh465388.aspx#attribute_section if ( div.querySelectorAll("[msallowclip^='']").length ) { rbuggyQSA.push( "[*^$]=" + whitespace + "*(?:''|\"\")" ); } // Support: IE8 // Boolean attributes and "value" are not treated correctly if ( !div.querySelectorAll("[selected]").length ) { rbuggyQSA.push( "\\[" + whitespace + "*(?:value|" + booleans + ")" ); } // Webkit/Opera - :checked should return selected option elements // http://www.w3.org/TR/2011/REC-css3-selectors-20110929/#checked // IE8 throws error here and will not see later tests if ( !div.querySelectorAll(":checked").length ) { rbuggyQSA.push(":checked"); } }); assert(function( div ) { // Support: Windows 8 Native Apps // The type and name attributes are restricted during .innerHTML assignment var input = doc.createElement("input"); input.setAttribute( "type", "hidden" ); div.appendChild( input ).setAttribute( "name", "D" ); // Support: IE8 // Enforce case-sensitivity of name attribute if ( div.querySelectorAll("[name=d]").length ) { rbuggyQSA.push( "name" + whitespace + "*[*^$|!~]?=" ); } // FF 3.5 - :enabled/:disabled and hidden elements (hidden elements are still enabled) // IE8 throws error here and will not see later tests if ( !div.querySelectorAll(":enabled").length ) { rbuggyQSA.push( ":enabled", ":disabled" ); } // Opera 10-11 does not throw on post-comma invalid pseudos div.querySelectorAll("*,:x"); rbuggyQSA.push(",.*:"); }); } if ( (support.matchesSelector = rnative.test( (matches = docElem.matches || docElem.webkitMatchesSelector || docElem.mozMatchesSelector || docElem.oMatchesSelector || docElem.msMatchesSelector) )) ) { assert(function( div ) { // Check to see if it's possible to do matchesSelector // on a disconnected node (IE 9) support.disconnectedMatch = matches.call( div, "div" ); // This should fail with an exception // Gecko does not error, returns false instead matches.call( div, "[s!='']:x" ); rbuggyMatches.push( "!=", pseudos ); }); } rbuggyQSA = rbuggyQSA.length && new RegExp( rbuggyQSA.join("|") ); rbuggyMatches = rbuggyMatches.length && new RegExp( rbuggyMatches.join("|") ); /* Contains ---------------------------------------------------------------------- */ hasCompare = rnative.test( docElem.compareDocumentPosition ); // Element contains another // Purposefully does not implement inclusive descendent // As in, an element does not contain itself contains = hasCompare || rnative.test( docElem.contains ) ? function( a, b ) { var adown = a.nodeType === 9 ? a.documentElement : a, bup = b && b.parentNode; return a === bup || !!( bup && bup.nodeType === 1 && ( adown.contains ? adown.contains( bup ) : a.compareDocumentPosition && a.compareDocumentPosition( bup ) & 16 )); } : function( a, b ) { if ( b ) { while ( (b = b.parentNode) ) { if ( b === a ) { return true; } } } return false; }; /* Sorting ---------------------------------------------------------------------- */ // Document order sorting sortOrder = hasCompare ? function( a, b ) { // Flag for duplicate removal if ( a === b ) { hasDuplicate = true; return 0; } // Sort on method existence if only one input has compareDocumentPosition var compare = !a.compareDocumentPosition - !b.compareDocumentPosition; if ( compare ) { return compare; } // Calculate position if both inputs belong to the same document compare = ( a.ownerDocument || a ) === ( b.ownerDocument || b ) ? a.compareDocumentPosition( b ) : // Otherwise we know they are disconnected 1; // Disconnected nodes if ( compare & 1 || (!support.sortDetached && b.compareDocumentPosition( a ) === compare) ) { // Choose the first element that is related to our preferred document if ( a === doc || a.ownerDocument === preferredDoc && contains(preferredDoc, a) ) { return -1; } if ( b === doc || b.ownerDocument === preferredDoc && contains(preferredDoc, b) ) { return 1; } // Maintain original order return sortInput ? ( indexOf.call( sortInput, a ) - indexOf.call( sortInput, b ) ) : 0; } return compare & 4 ? -1 : 1; } : function( a, b ) { // Exit early if the nodes are identical if ( a === b ) { hasDuplicate = true; return 0; } var cur, i = 0, aup = a.parentNode, bup = b.parentNode, ap = [ a ], bp = [ b ]; // Parentless nodes are either documents or disconnected if ( !aup || !bup ) { return a === doc ? -1 : b === doc ? 1 : aup ? -1 : bup ? 1 : sortInput ? ( indexOf.call( sortInput, a ) - indexOf.call( sortInput, b ) ) : 0; // If the nodes are siblings, we can do a quick check } else if ( aup === bup ) { return siblingCheck( a, b ); } // Otherwise we need full lists of their ancestors for comparison cur = a; while ( (cur = cur.parentNode) ) { ap.unshift( cur ); } cur = b; while ( (cur = cur.parentNode) ) { bp.unshift( cur ); } // Walk down the tree looking for a discrepancy while ( ap[i] === bp[i] ) { i++; } return i ? // Do a sibling check if the nodes have a common ancestor siblingCheck( ap[i], bp[i] ) : // Otherwise nodes in our document sort first ap[i] === preferredDoc ? -1 : bp[i] === preferredDoc ? 1 : 0; }; return doc; }; Sizzle.matches = function( expr, elements ) { return Sizzle( expr, null, null, elements ); }; Sizzle.matchesSelector = function( elem, expr ) { // Set document vars if needed if ( ( elem.ownerDocument || elem ) !== document ) { setDocument( elem ); } // Make sure that attribute selectors are quoted expr = expr.replace( rattributeQuotes, "='$1']" ); if ( support.matchesSelector && documentIsHTML && ( !rbuggyMatches || !rbuggyMatches.test( expr ) ) && ( !rbuggyQSA || !rbuggyQSA.test( expr ) ) ) { try { var ret = matches.call( elem, expr ); // IE 9's matchesSelector returns false on disconnected nodes if ( ret || support.disconnectedMatch || // As well, disconnected nodes are said to be in a document // fragment in IE 9 elem.document && elem.document.nodeType !== 11 ) { return ret; } } catch(e) {} } return Sizzle( expr, document, null, [ elem ] ).length > 0; }; Sizzle.contains = function( context, elem ) { // Set document vars if needed if ( ( context.ownerDocument || context ) !== document ) { setDocument( context ); } return contains( context, elem ); }; Sizzle.attr = function( elem, name ) { // Set document vars if needed if ( ( elem.ownerDocument || elem ) !== document ) { setDocument( elem ); } var fn = Expr.attrHandle[ name.toLowerCase() ], // Don't get fooled by Object.prototype properties (jQuery #13807) val = fn && hasOwn.call( Expr.attrHandle, name.toLowerCase() ) ? fn( elem, name, !documentIsHTML ) : undefined; return val !== undefined ? val : support.attributes || !documentIsHTML ? elem.getAttribute( name ) : (val = elem.getAttributeNode(name)) && val.specified ? val.value : null; }; Sizzle.error = function( msg ) { throw new Error( "Syntax error, unrecognized expression: " + msg ); }; /** * Document sorting and removing duplicates * @param {ArrayLike} results */ Sizzle.uniqueSort = function( results ) { var elem, duplicates = [], j = 0, i = 0; // Unless we *know* we can detect duplicates, assume their presence hasDuplicate = !support.detectDuplicates; sortInput = !support.sortStable && results.slice( 0 ); results.sort( sortOrder ); if ( hasDuplicate ) { while ( (elem = results[i++]) ) { if ( elem === results[ i ] ) { j = duplicates.push( i ); } } while ( j-- ) { results.splice( duplicates[ j ], 1 ); } } // Clear input after sorting to release objects // See https://github.com/jquery/sizzle/pull/225 sortInput = null; return results; }; /** * Utility function for retrieving the text value of an array of DOM nodes * @param {Array|Element} elem */ getText = Sizzle.getText = function( elem ) { var node, ret = "", i = 0, nodeType = elem.nodeType; if ( !nodeType ) { // If no nodeType, this is expected to be an array while ( (node = elem[i++]) ) { // Do not traverse comment nodes ret += getText( node ); } } else if ( nodeType === 1 || nodeType === 9 || nodeType === 11 ) { // Use textContent for elements // innerText usage removed for consistency of new lines (jQuery #11153) if ( typeof elem.textContent === "string" ) { return elem.textContent; } else { // Traverse its children for ( elem = elem.firstChild; elem; elem = elem.nextSibling ) { ret += getText( elem ); } } } else if ( nodeType === 3 || nodeType === 4 ) { return elem.nodeValue; } // Do not include comment or processing instruction nodes return ret; }; Expr = Sizzle.selectors = { // Can be adjusted by the user cacheLength: 50, createPseudo: markFunction, match: matchExpr, attrHandle: {}, find: {}, relative: { ">": { dir: "parentNode", first: true }, " ": { dir: "parentNode" }, "+": { dir: "previousSibling", first: true }, "~": { dir: "previousSibling" } }, preFilter: { "ATTR": function( match ) { match[1] = match[1].replace( runescape, funescape ); // Move the given value to match[3] whether quoted or unquoted match[3] = ( match[3] || match[4] || match[5] || "" ).replace( runescape, funescape ); if ( match[2] === "~=" ) { match[3] = " " + match[3] + " "; } return match.slice( 0, 4 ); }, "CHILD": function( match ) { /* matches from matchExpr["CHILD"] 1 type (only|nth|...) 2 what (child|of-type) 3 argument (even|odd|\d*|\d*n([+-]\d+)?|...) 4 xn-component of xn+y argument ([+-]?\d*n|) 5 sign of xn-component 6 x of xn-component 7 sign of y-component 8 y of y-component */ match[1] = match[1].toLowerCase(); if ( match[1].slice( 0, 3 ) === "nth" ) { // nth-* requires argument if ( !match[3] ) { Sizzle.error( match[0] ); } // numeric x and y parameters for Expr.filter.CHILD // remember that false/true cast respectively to 0/1 match[4] = +( match[4] ? match[5] + (match[6] || 1) : 2 * ( match[3] === "even" || match[3] === "odd" ) ); match[5] = +( ( match[7] + match[8] ) || match[3] === "odd" ); // other types prohibit arguments } else if ( match[3] ) { Sizzle.error( match[0] ); } return match; }, "PSEUDO": function( match ) { var excess, unquoted = !match[6] && match[2]; if ( matchExpr["CHILD"].test( match[0] ) ) { return null; } // Accept quoted arguments as-is if ( match[3] ) { match[2] = match[4] || match[5] || ""; // Strip excess characters from unquoted arguments } else if ( unquoted && rpseudo.test( unquoted ) && // Get excess from tokenize (recursively) (excess = tokenize( unquoted, true )) && // advance to the next closing parenthesis (excess = unquoted.indexOf( ")", unquoted.length - excess ) - unquoted.length) ) { // excess is a negative index match[0] = match[0].slice( 0, excess ); match[2] = unquoted.slice( 0, excess ); } // Return only captures needed by the pseudo filter method (type and argument) return match.slice( 0, 3 ); } }, filter: { "TAG": function( nodeNameSelector ) { var nodeName = nodeNameSelector.replace( runescape, funescape ).toLowerCase(); return nodeNameSelector === "*" ? function() { return true; } : function( elem ) { return elem.nodeName && elem.nodeName.toLowerCase() === nodeName; }; }, "CLASS": function( className ) { var pattern = classCache[ className + " " ]; return pattern || (pattern = new RegExp( "(^|" + whitespace + ")" + className + "(" + whitespace + "|$)" )) && classCache( className, function( elem ) { return pattern.test( typeof elem.className === "string" && elem.className || typeof elem.getAttribute !== strundefined && elem.getAttribute("class") || "" ); }); }, "ATTR": function( name, operator, check ) { return function( elem ) { var result = Sizzle.attr( elem, name ); if ( result == null ) { return operator === "!="; } if ( !operator ) { return true; } result += ""; return operator === "=" ? result === check : operator === "!=" ? result !== check : operator === "^=" ? check && result.indexOf( check ) === 0 : operator === "*=" ? check && result.indexOf( check ) > -1 : operator === "$=" ? check && result.slice( -check.length ) === check : operator === "~=" ? ( " " + result + " " ).indexOf( check ) > -1 : operator === "|=" ? result === check || result.slice( 0, check.length + 1 ) === check + "-" : false; }; }, "CHILD": function( type, what, argument, first, last ) { var simple = type.slice( 0, 3 ) !== "nth", forward = type.slice( -4 ) !== "last", ofType = what === "of-type"; return first === 1 && last === 0 ? // Shortcut for :nth-*(n) function( elem ) { return !!elem.parentNode; } : function( elem, context, xml ) { var cache, outerCache, node, diff, nodeIndex, start, dir = simple !== forward ? "nextSibling" : "previousSibling", parent = elem.parentNode, name = ofType && elem.nodeName.toLowerCase(), useCache = !xml && !ofType; if ( parent ) { // :(first|last|only)-(child|of-type) if ( simple ) { while ( dir ) { node = elem; while ( (node = node[ dir ]) ) { if ( ofType ? node.nodeName.toLowerCase() === name : node.nodeType === 1 ) { return false; } } // Reverse direction for :only-* (if we haven't yet done so) start = dir = type === "only" && !start && "nextSibling"; } return true; } start = [ forward ? parent.firstChild : parent.lastChild ]; // non-xml :nth-child(...) stores cache data on `parent` if ( forward && useCache ) { // Seek `elem` from a previously-cached index outerCache = parent[ expando ] || (parent[ expando ] = {}); cache = outerCache[ type ] || []; nodeIndex = cache[0] === dirruns && cache[1]; diff = cache[0] === dirruns && cache[2]; node = nodeIndex && parent.childNodes[ nodeIndex ]; while ( (node = ++nodeIndex && node && node[ dir ] || // Fallback to seeking `elem` from the start (diff = nodeIndex = 0) || start.pop()) ) { // When found, cache indexes on `parent` and break if ( node.nodeType === 1 && ++diff && node === elem ) { outerCache[ type ] = [ dirruns, nodeIndex, diff ]; break; } } // Use previously-cached element index if available } else if ( useCache && (cache = (elem[ expando ] || (elem[ expando ] = {}))[ type ]) && cache[0] === dirruns ) { diff = cache[1]; // xml :nth-child(...) or :nth-last-child(...) or :nth(-last)?-of-type(...) } else { // Use the same loop as above to seek `elem` from the start while ( (node = ++nodeIndex && node && node[ dir ] || (diff = nodeIndex = 0) || start.pop()) ) { if ( ( ofType ? node.nodeName.toLowerCase() === name : node.nodeType === 1 ) && ++diff ) { // Cache the index of each encountered element if ( useCache ) { (node[ expando ] || (node[ expando ] = {}))[ type ] = [ dirruns, diff ]; } if ( node === elem ) { break; } } } } // Incorporate the offset, then check against cycle size diff -= last; return diff === first || ( diff % first === 0 && diff / first >= 0 ); } }; }, "PSEUDO": function( pseudo, argument ) { // pseudo-class names are case-insensitive // http://www.w3.org/TR/selectors/#pseudo-classes // Prioritize by case sensitivity in case custom pseudos are added with uppercase letters // Remember that setFilters inherits from pseudos var args, fn = Expr.pseudos[ pseudo ] || Expr.setFilters[ pseudo.toLowerCase() ] || Sizzle.error( "unsupported pseudo: " + pseudo ); // The user may use createPseudo to indicate that // arguments are needed to create the filter function // just as Sizzle does if ( fn[ expando ] ) { return fn( argument ); } // But maintain support for old signatures if ( fn.length > 1 ) { args = [ pseudo, pseudo, "", argument ]; return Expr.setFilters.hasOwnProperty( pseudo.toLowerCase() ) ? markFunction(function( seed, matches ) { var idx, matched = fn( seed, argument ), i = matched.length; while ( i-- ) { idx = indexOf.call( seed, matched[i] ); seed[ idx ] = !( matches[ idx ] = matched[i] ); } }) : function( elem ) { return fn( elem, 0, args ); }; } return fn; } }, pseudos: { // Potentially complex pseudos "not": markFunction(function( selector ) { // Trim the selector passed to compile // to avoid treating leading and trailing // spaces as combinators var input = [], results = [], matcher = compile( selector.replace( rtrim, "$1" ) ); return matcher[ expando ] ? markFunction(function( seed, matches, context, xml ) { var elem, unmatched = matcher( seed, null, xml, [] ), i = seed.length; // Match elements unmatched by `matcher` while ( i-- ) { if ( (elem = unmatched[i]) ) { seed[i] = !(matches[i] = elem); } } }) : function( elem, context, xml ) { input[0] = elem; matcher( input, null, xml, results ); return !results.pop(); }; }), "has": markFunction(function( selector ) { return function( elem ) { return Sizzle( selector, elem ).length > 0; }; }), "contains": markFunction(function( text ) { return function( elem ) { return ( elem.textContent || elem.innerText || getText( elem ) ).indexOf( text ) > -1; }; }), // "Whether an element is represented by a :lang() selector // is based solely on the element's language value // being equal to the identifier C, // or beginning with the identifier C immediately followed by "-". // The matching of C against the element's language value is performed case-insensitively. // The identifier C does not have to be a valid language name." // http://www.w3.org/TR/selectors/#lang-pseudo "lang": markFunction( function( lang ) { // lang value must be a valid identifier if ( !ridentifier.test(lang || "") ) { Sizzle.error( "unsupported lang: " + lang ); } lang = lang.replace( runescape, funescape ).toLowerCase(); return function( elem ) { var elemLang; do { if ( (elemLang = documentIsHTML ? elem.lang : elem.getAttribute("xml:lang") || elem.getAttribute("lang")) ) { elemLang = elemLang.toLowerCase(); return elemLang === lang || elemLang.indexOf( lang + "-" ) === 0; } } while ( (elem = elem.parentNode) && elem.nodeType === 1 ); return false; }; }), // Miscellaneous "target": function( elem ) { var hash = window.location && window.location.hash; return hash && hash.slice( 1 ) === elem.id; }, "root": function( elem ) { return elem === docElem; }, "focus": function( elem ) { return elem === document.activeElement && (!document.hasFocus || document.hasFocus()) && !!(elem.type || elem.href || ~elem.tabIndex); }, // Boolean properties "enabled": function( elem ) { return elem.disabled === false; }, "disabled": function( elem ) { return elem.disabled === true; }, "checked": function( elem ) { // In CSS3, :checked should return both checked and selected elements // http://www.w3.org/TR/2011/REC-css3-selectors-20110929/#checked var nodeName = elem.nodeName.toLowerCase(); return (nodeName === "input" && !!elem.checked) || (nodeName === "option" && !!elem.selected); }, "selected": function( elem ) { // Accessing this property makes selected-by-default // options in Safari work properly if ( elem.parentNode ) { elem.parentNode.selectedIndex; } return elem.selected === true; }, // Contents "empty": function( elem ) { // http://www.w3.org/TR/selectors/#empty-pseudo // :empty is negated by element (1) or content nodes (text: 3; cdata: 4; entity ref: 5), // but not by others (comment: 8; processing instruction: 7; etc.) // nodeType < 6 works because attributes (2) do not appear as children for ( elem = elem.firstChild; elem; elem = elem.nextSibling ) { if ( elem.nodeType < 6 ) { return false; } } return true; }, "parent": function( elem ) { return !Expr.pseudos["empty"]( elem ); }, // Element/input types "header": function( elem ) { return rheader.test( elem.nodeName ); }, "input": function( elem ) { return rinputs.test( elem.nodeName ); }, "button": function( elem ) { var name = elem.nodeName.toLowerCase(); return name === "input" && elem.type === "button" || name === "button"; }, "text": function( elem ) { var attr; return elem.nodeName.toLowerCase() === "input" && elem.type === "text" && // Support: IE<8 // New HTML5 attribute values (e.g., "search") appear with elem.type === "text" ( (attr = elem.getAttribute("type")) == null || attr.toLowerCase() === "text" ); }, // Position-in-collection "first": createPositionalPseudo(function() { return [ 0 ]; }), "last": createPositionalPseudo(function( matchIndexes, length ) { return [ length - 1 ]; }), "eq": createPositionalPseudo(function( matchIndexes, length, argument ) { return [ argument < 0 ? argument + length : argument ]; }), "even": createPositionalPseudo(function( matchIndexes, length ) { var i = 0; for ( ; i < length; i += 2 ) { matchIndexes.push( i ); } return matchIndexes; }), "odd": createPositionalPseudo(function( matchIndexes, length ) { var i = 1; for ( ; i < length; i += 2 ) { matchIndexes.push( i ); } return matchIndexes; }), "lt": createPositionalPseudo(function( matchIndexes, length, argument ) { var i = argument < 0 ? argument + length : argument; for ( ; --i >= 0; ) { matchIndexes.push( i ); } return matchIndexes; }), "gt": createPositionalPseudo(function( matchIndexes, length, argument ) { var i = argument < 0 ? argument + length : argument; for ( ; ++i < length; ) { matchIndexes.push( i ); } return matchIndexes; }) } }; Expr.pseudos["nth"] = Expr.pseudos["eq"]; // Add button/input type pseudos for ( i in { radio: true, checkbox: true, file: true, password: true, image: true } ) { Expr.pseudos[ i ] = createInputPseudo( i ); } for ( i in { submit: true, reset: true } ) { Expr.pseudos[ i ] = createButtonPseudo( i ); } // Easy API for creating new setFilters function setFilters() {} setFilters.prototype = Expr.filters = Expr.pseudos; Expr.setFilters = new setFilters(); tokenize = Sizzle.tokenize = function( selector, parseOnly ) { var matched, match, tokens, type, soFar, groups, preFilters, cached = tokenCache[ selector + " " ]; if ( cached ) { return parseOnly ? 0 : cached.slice( 0 ); } soFar = selector; groups = []; preFilters = Expr.preFilter; while ( soFar ) { // Comma and first run if ( !matched || (match = rcomma.exec( soFar )) ) { if ( match ) { // Don't consume trailing commas as valid soFar = soFar.slice( match[0].length ) || soFar; } groups.push( (tokens = []) ); } matched = false; // Combinators if ( (match = rcombinators.exec( soFar )) ) { matched = match.shift(); tokens.push({ value: matched, // Cast descendant combinators to space type: match[0].replace( rtrim, " " ) }); soFar = soFar.slice( matched.length ); } // Filters for ( type in Expr.filter ) { if ( (match = matchExpr[ type ].exec( soFar )) && (!preFilters[ type ] || (match = preFilters[ type ]( match ))) ) { matched = match.shift(); tokens.push({ value: matched, type: type, matches: match }); soFar = soFar.slice( matched.length ); } } if ( !matched ) { break; } } // Return the length of the invalid excess // if we're just parsing // Otherwise, throw an error or return tokens return parseOnly ? soFar.length : soFar ? Sizzle.error( selector ) : // Cache the tokens tokenCache( selector, groups ).slice( 0 ); }; function toSelector( tokens ) { var i = 0, len = tokens.length, selector = ""; for ( ; i < len; i++ ) { selector += tokens[i].value; } return selector; } function addCombinator( matcher, combinator, base ) { var dir = combinator.dir, checkNonElements = base && dir === "parentNode", doneName = done++; return combinator.first ? // Check against closest ancestor/preceding element function( elem, context, xml ) { while ( (elem = elem[ dir ]) ) { if ( elem.nodeType === 1 || checkNonElements ) { return matcher( elem, context, xml ); } } } : // Check against all ancestor/preceding elements function( elem, context, xml ) { var oldCache, outerCache, newCache = [ dirruns, doneName ]; // We can't set arbitrary data on XML nodes, so they don't benefit from dir caching if ( xml ) { while ( (elem = elem[ dir ]) ) { if ( elem.nodeType === 1 || checkNonElements ) { if ( matcher( elem, context, xml ) ) { return true; } } } } else { while ( (elem = elem[ dir ]) ) { if ( elem.nodeType === 1 || checkNonElements ) { outerCache = elem[ expando ] || (elem[ expando ] = {}); if ( (oldCache = outerCache[ dir ]) && oldCache[ 0 ] === dirruns && oldCache[ 1 ] === doneName ) { // Assign to newCache so results back-propagate to previous elements return (newCache[ 2 ] = oldCache[ 2 ]); } else { // Reuse newcache so results back-propagate to previous elements outerCache[ dir ] = newCache; // A match means we're done; a fail means we have to keep checking if ( (newCache[ 2 ] = matcher( elem, context, xml )) ) { return true; } } } } } }; } function elementMatcher( matchers ) { return matchers.length > 1 ? function( elem, context, xml ) { var i = matchers.length; while ( i-- ) { if ( !matchers[i]( elem, context, xml ) ) { return false; } } return true; } : matchers[0]; } function multipleContexts( selector, contexts, results ) { var i = 0, len = contexts.length; for ( ; i < len; i++ ) { Sizzle( selector, contexts[i], results ); } return results; } function condense( unmatched, map, filter, context, xml ) { var elem, newUnmatched = [], i = 0, len = unmatched.length, mapped = map != null; for ( ; i < len; i++ ) { if ( (elem = unmatched[i]) ) { if ( !filter || filter( elem, context, xml ) ) { newUnmatched.push( elem ); if ( mapped ) { map.push( i ); } } } } return newUnmatched; } function setMatcher( preFilter, selector, matcher, postFilter, postFinder, postSelector ) { if ( postFilter && !postFilter[ expando ] ) { postFilter = setMatcher( postFilter ); } if ( postFinder && !postFinder[ expando ] ) { postFinder = setMatcher( postFinder, postSelector ); } return markFunction(function( seed, results, context, xml ) { var temp, i, elem, preMap = [], postMap = [], preexisting = results.length, // Get initial elements from seed or context elems = seed || multipleContexts( selector || "*", context.nodeType ? [ context ] : context, [] ), // Prefilter to get matcher input, preserving a map for seed-results synchronization matcherIn = preFilter && ( seed || !selector ) ? condense( elems, preMap, preFilter, context, xml ) : elems, matcherOut = matcher ? // If we have a postFinder, or filtered seed, or non-seed postFilter or preexisting results, postFinder || ( seed ? preFilter : preexisting || postFilter ) ? // ...intermediate processing is necessary [] : // ...otherwise use results directly results : matcherIn; // Find primary matches if ( matcher ) { matcher( matcherIn, matcherOut, context, xml ); } // Apply postFilter if ( postFilter ) { temp = condense( matcherOut, postMap ); postFilter( temp, [], context, xml ); // Un-match failing elements by moving them back to matcherIn i = temp.length; while ( i-- ) { if ( (elem = temp[i]) ) { matcherOut[ postMap[i] ] = !(matcherIn[ postMap[i] ] = elem); } } } if ( seed ) { if ( postFinder || preFilter ) { if ( postFinder ) { // Get the final matcherOut by condensing this intermediate into postFinder contexts temp = []; i = matcherOut.length; while ( i-- ) { if ( (elem = matcherOut[i]) ) { // Restore matcherIn since elem is not yet a final match temp.push( (matcherIn[i] = elem) ); } } postFinder( null, (matcherOut = []), temp, xml ); } // Move matched elements from seed to results to keep them synchronized i = matcherOut.length; while ( i-- ) { if ( (elem = matcherOut[i]) && (temp = postFinder ? indexOf.call( seed, elem ) : preMap[i]) > -1 ) { seed[temp] = !(results[temp] = elem); } } } // Add elements to results, through postFinder if defined } else { matcherOut = condense( matcherOut === results ? matcherOut.splice( preexisting, matcherOut.length ) : matcherOut ); if ( postFinder ) { postFinder( null, results, matcherOut, xml ); } else { push.apply( results, matcherOut ); } } }); } function matcherFromTokens( tokens ) { var checkContext, matcher, j, len = tokens.length, leadingRelative = Expr.relative[ tokens[0].type ], implicitRelative = leadingRelative || Expr.relative[" "], i = leadingRelative ? 1 : 0, // The foundational matcher ensures that elements are reachable from top-level context(s) matchContext = addCombinator( function( elem ) { return elem === checkContext; }, implicitRelative, true ), matchAnyContext = addCombinator( function( elem ) { return indexOf.call( checkContext, elem ) > -1; }, implicitRelative, true ), matchers = [ function( elem, context, xml ) { return ( !leadingRelative && ( xml || context !== outermostContext ) ) || ( (checkContext = context).nodeType ? matchContext( elem, context, xml ) : matchAnyContext( elem, context, xml ) ); } ]; for ( ; i < len; i++ ) { if ( (matcher = Expr.relative[ tokens[i].type ]) ) { matchers = [ addCombinator(elementMatcher( matchers ), matcher) ]; } else { matcher = Expr.filter[ tokens[i].type ].apply( null, tokens[i].matches ); // Return special upon seeing a positional matcher if ( matcher[ expando ] ) { // Find the next relative operator (if any) for proper handling j = ++i; for ( ; j < len; j++ ) { if ( Expr.relative[ tokens[j].type ] ) { break; } } return setMatcher( i > 1 && elementMatcher( matchers ), i > 1 && toSelector( // If the preceding token was a descendant combinator, insert an implicit any-element `*` tokens.slice( 0, i - 1 ).concat({ value: tokens[ i - 2 ].type === " " ? "*" : "" }) ).replace( rtrim, "$1" ), matcher, i < j && matcherFromTokens( tokens.slice( i, j ) ), j < len && matcherFromTokens( (tokens = tokens.slice( j )) ), j < len && toSelector( tokens ) ); } matchers.push( matcher ); } } return elementMatcher( matchers ); } function matcherFromGroupMatchers( elementMatchers, setMatchers ) { var bySet = setMatchers.length > 0, byElement = elementMatchers.length > 0, superMatcher = function( seed, context, xml, results, outermost ) { var elem, j, matcher, matchedCount = 0, i = "0", unmatched = seed && [], setMatched = [], contextBackup = outermostContext, // We must always have either seed elements or outermost context elems = seed || byElement && Expr.find["TAG"]( "*", outermost ), // Use integer dirruns iff this is the outermost matcher dirrunsUnique = (dirruns += contextBackup == null ? 1 : Math.random() || 0.1), len = elems.length; if ( outermost ) { outermostContext = context !== document && context; } // Add elements passing elementMatchers directly to results // Keep `i` a string if there are no elements so `matchedCount` will be "00" below // Support: IE<9, Safari // Tolerate NodeList properties (IE: "length"; Safari: ) matching elements by id for ( ; i !== len && (elem = elems[i]) != null; i++ ) { if ( byElement && elem ) { j = 0; while ( (matcher = elementMatchers[j++]) ) { if ( matcher( elem, context, xml ) ) { results.push( elem ); break; } } if ( outermost ) { dirruns = dirrunsUnique; } } // Track unmatched elements for set filters if ( bySet ) { // They will have gone through all possible matchers if ( (elem = !matcher && elem) ) { matchedCount--; } // Lengthen the array for every element, matched or not if ( seed ) { unmatched.push( elem ); } } } // Apply set filters to unmatched elements matchedCount += i; if ( bySet && i !== matchedCount ) { j = 0; while ( (matcher = setMatchers[j++]) ) { matcher( unmatched, setMatched, context, xml ); } if ( seed ) { // Reintegrate element matches to eliminate the need for sorting if ( matchedCount > 0 ) { while ( i-- ) { if ( !(unmatched[i] || setMatched[i]) ) { setMatched[i] = pop.call( results ); } } } // Discard index placeholder values to get only actual matches setMatched = condense( setMatched ); } // Add matches to results push.apply( results, setMatched ); // Seedless set matches succeeding multiple successful matchers stipulate sorting if ( outermost && !seed && setMatched.length > 0 && ( matchedCount + setMatchers.length ) > 1 ) { Sizzle.uniqueSort( results ); } } // Override manipulation of globals by nested matchers if ( outermost ) { dirruns = dirrunsUnique; outermostContext = contextBackup; } return unmatched; }; return bySet ? markFunction( superMatcher ) : superMatcher; } compile = Sizzle.compile = function( selector, match /* Internal Use Only */ ) { var i, setMatchers = [], elementMatchers = [], cached = compilerCache[ selector + " " ]; if ( !cached ) { // Generate a function of recursive functions that can be used to check each element if ( !match ) { match = tokenize( selector ); } i = match.length; while ( i-- ) { cached = matcherFromTokens( match[i] ); if ( cached[ expando ] ) { setMatchers.push( cached ); } else { elementMatchers.push( cached ); } } // Cache the compiled function cached = compilerCache( selector, matcherFromGroupMatchers( elementMatchers, setMatchers ) ); // Save selector and tokenization cached.selector = selector; } return cached; }; /** * A low-level selection function that works with Sizzle's compiled * selector functions * @param {String|Function} selector A selector or a pre-compiled * selector function built with Sizzle.compile * @param {Element} context * @param {Array} [results] * @param {Array} [seed] A set of elements to match against */ select = Sizzle.select = function( selector, context, results, seed ) { var i, tokens, token, type, find, compiled = typeof selector === "function" && selector, match = !seed && tokenize( (selector = compiled.selector || selector) ); results = results || []; // Try to minimize operations if there is no seed and only one group if ( match.length === 1 ) { // Take a shortcut and set the context if the root selector is an ID tokens = match[0] = match[0].slice( 0 ); if ( tokens.length > 2 && (token = tokens[0]).type === "ID" && support.getById && context.nodeType === 9 && documentIsHTML && Expr.relative[ tokens[1].type ] ) { context = ( Expr.find["ID"]( token.matches[0].replace(runescape, funescape), context ) || [] )[0]; if ( !context ) { return results; // Precompiled matchers will still verify ancestry, so step up a level } else if ( compiled ) { context = context.parentNode; } selector = selector.slice( tokens.shift().value.length ); } // Fetch a seed set for right-to-left matching i = matchExpr["needsContext"].test( selector ) ? 0 : tokens.length; while ( i-- ) { token = tokens[i]; // Abort if we hit a combinator if ( Expr.relative[ (type = token.type) ] ) { break; } if ( (find = Expr.find[ type ]) ) { // Search, expanding context for leading sibling combinators if ( (seed = find( token.matches[0].replace( runescape, funescape ), rsibling.test( tokens[0].type ) && testContext( context.parentNode ) || context )) ) { // If seed is empty or no tokens remain, we can return early tokens.splice( i, 1 ); selector = seed.length && toSelector( tokens ); if ( !selector ) { push.apply( results, seed ); return results; } break; } } } } // Compile and execute a filtering function if one is not provided // Provide `match` to avoid retokenization if we modified the selector above ( compiled || compile( selector, match ) )( seed, context, !documentIsHTML, results, rsibling.test( selector ) && testContext( context.parentNode ) || context ); return results; }; // One-time assignments // Sort stability support.sortStable = expando.split("").sort( sortOrder ).join("") === expando; // Support: Chrome<14 // Always assume duplicates if they aren't passed to the comparison function support.detectDuplicates = !!hasDuplicate; // Initialize against the default document setDocument(); // Support: Webkit<537.32 - Safari 6.0.3/Chrome 25 (fixed in Chrome 27) // Detached nodes confoundingly follow *each other* support.sortDetached = assert(function( div1 ) { // Should return 1, but returns 4 (following) return div1.compareDocumentPosition( document.createElement("div") ) & 1; }); // Support: IE<8 // Prevent attribute/property "interpolation" // http://msdn.microsoft.com/en-us/library/ms536429%28VS.85%29.aspx if ( !assert(function( div ) { div.innerHTML = ""; return div.firstChild.getAttribute("href") === "#" ; }) ) { addHandle( "type|href|height|width", function( elem, name, isXML ) { if ( !isXML ) { return elem.getAttribute( name, name.toLowerCase() === "type" ? 1 : 2 ); } }); } // Support: IE<9 // Use defaultValue in place of getAttribute("value") if ( !support.attributes || !assert(function( div ) { div.innerHTML = ""; div.firstChild.setAttribute( "value", "" ); return div.firstChild.getAttribute( "value" ) === ""; }) ) { addHandle( "value", function( elem, name, isXML ) { if ( !isXML && elem.nodeName.toLowerCase() === "input" ) { return elem.defaultValue; } }); } // Support: IE<9 // Use getAttributeNode to fetch booleans when getAttribute lies if ( !assert(function( div ) { return div.getAttribute("disabled") == null; }) ) { addHandle( booleans, function( elem, name, isXML ) { var val; if ( !isXML ) { return elem[ name ] === true ? name.toLowerCase() : (val = elem.getAttributeNode( name )) && val.specified ? val.value : null; } }); } return Sizzle; })( window ); jQuery.find = Sizzle; jQuery.expr = Sizzle.selectors; jQuery.expr[":"] = jQuery.expr.pseudos; jQuery.unique = Sizzle.uniqueSort; jQuery.text = Sizzle.getText; jQuery.isXMLDoc = Sizzle.isXML; jQuery.contains = Sizzle.contains; var rneedsContext = jQuery.expr.match.needsContext; var rsingleTag = (/^<(\w+)\s*\/?>(?:<\/\1>|)$/); var risSimple = /^.[^:#\[\.,]*$/; // Implement the identical functionality for filter and not function winnow( elements, qualifier, not ) { if ( jQuery.isFunction( qualifier ) ) { return jQuery.grep( elements, function( elem, i ) { /* jshint -W018 */ return !!qualifier.call( elem, i, elem ) !== not; }); } if ( qualifier.nodeType ) { return jQuery.grep( elements, function( elem ) { return ( elem === qualifier ) !== not; }); } if ( typeof qualifier === "string" ) { if ( risSimple.test( qualifier ) ) { return jQuery.filter( qualifier, elements, not ); } qualifier = jQuery.filter( qualifier, elements ); } return jQuery.grep( elements, function( elem ) { return ( indexOf.call( qualifier, elem ) >= 0 ) !== not; }); } jQuery.filter = function( expr, elems, not ) { var elem = elems[ 0 ]; if ( not ) { expr = ":not(" + expr + ")"; } return elems.length === 1 && elem.nodeType === 1 ? jQuery.find.matchesSelector( elem, expr ) ? [ elem ] : [] : jQuery.find.matches( expr, jQuery.grep( elems, function( elem ) { return elem.nodeType === 1; })); }; jQuery.fn.extend({ find: function( selector ) { var i, len = this.length, ret = [], self = this; if ( typeof selector !== "string" ) { return this.pushStack( jQuery( selector ).filter(function() { for ( i = 0; i < len; i++ ) { if ( jQuery.contains( self[ i ], this ) ) { return true; } } }) ); } for ( i = 0; i < len; i++ ) { jQuery.find( selector, self[ i ], ret ); } // Needed because $( selector, context ) becomes $( context ).find( selector ) ret = this.pushStack( len > 1 ? jQuery.unique( ret ) : ret ); ret.selector = this.selector ? this.selector + " " + selector : selector; return ret; }, filter: function( selector ) { return this.pushStack( winnow(this, selector || [], false) ); }, not: function( selector ) { return this.pushStack( winnow(this, selector || [], true) ); }, is: function( selector ) { return !!winnow( this, // If this is a positional/relative selector, check membership in the returned set // so $("p:first").is("p:last") won't return true for a doc with two "p". typeof selector === "string" && rneedsContext.test( selector ) ? jQuery( selector ) : selector || [], false ).length; } }); // Initialize a jQuery object // A central reference to the root jQuery(document) var rootjQuery, // A simple way to check for HTML strings // Prioritize #id over to avoid XSS via location.hash (#9521) // Strict HTML recognition (#11290: must start with <) rquickExpr = /^(?:\s*(<[\w\W]+>)[^>]*|#([\w-]*))$/, init = jQuery.fn.init = function( selector, context ) { var match, elem; // HANDLE: $(""), $(null), $(undefined), $(false) if ( !selector ) { return this; } // Handle HTML strings if ( typeof selector === "string" ) { if ( selector[0] === "<" && selector[ selector.length - 1 ] === ">" && selector.length >= 3 ) { // Assume that strings that start and end with <> are HTML and skip the regex check match = [ null, selector, null ]; } else { match = rquickExpr.exec( selector ); } // Match html or make sure no context is specified for #id if ( match && (match[1] || !context) ) { // HANDLE: $(html) -> $(array) if ( match[1] ) { context = context instanceof jQuery ? context[0] : context; // scripts is true for back-compat // Intentionally let the error be thrown if parseHTML is not present jQuery.merge( this, jQuery.parseHTML( match[1], context && context.nodeType ? context.ownerDocument || context : document, true ) ); // HANDLE: $(html, props) if ( rsingleTag.test( match[1] ) && jQuery.isPlainObject( context ) ) { for ( match in context ) { // Properties of context are called as methods if possible if ( jQuery.isFunction( this[ match ] ) ) { this[ match ]( context[ match ] ); // ...and otherwise set as attributes } else { this.attr( match, context[ match ] ); } } } return this; // HANDLE: $(#id) } else { elem = document.getElementById( match[2] ); // Check parentNode to catch when Blackberry 4.6 returns // nodes that are no longer in the document #6963 if ( elem && elem.parentNode ) { // Inject the element directly into the jQuery object this.length = 1; this[0] = elem; } this.context = document; this.selector = selector; return this; } // HANDLE: $(expr, $(...)) } else if ( !context || context.jquery ) { return ( context || rootjQuery ).find( selector ); // HANDLE: $(expr, context) // (which is just equivalent to: $(context).find(expr) } else { return this.constructor( context ).find( selector ); } // HANDLE: $(DOMElement) } else if ( selector.nodeType ) { this.context = this[0] = selector; this.length = 1; return this; // HANDLE: $(function) // Shortcut for document ready } else if ( jQuery.isFunction( selector ) ) { return typeof rootjQuery.ready !== "undefined" ? rootjQuery.ready( selector ) : // Execute immediately if ready is not present selector( jQuery ); } if ( selector.selector !== undefined ) { this.selector = selector.selector; this.context = selector.context; } return jQuery.makeArray( selector, this ); }; // Give the init function the jQuery prototype for later instantiation init.prototype = jQuery.fn; // Initialize central reference rootjQuery = jQuery( document ); var rparentsprev = /^(?:parents|prev(?:Until|All))/, // methods guaranteed to produce a unique set when starting from a unique set guaranteedUnique = { children: true, contents: true, next: true, prev: true }; jQuery.extend({ dir: function( elem, dir, until ) { var matched = [], truncate = until !== undefined; while ( (elem = elem[ dir ]) && elem.nodeType !== 9 ) { if ( elem.nodeType === 1 ) { if ( truncate && jQuery( elem ).is( until ) ) { break; } matched.push( elem ); } } return matched; }, sibling: function( n, elem ) { var matched = []; for ( ; n; n = n.nextSibling ) { if ( n.nodeType === 1 && n !== elem ) { matched.push( n ); } } return matched; } }); jQuery.fn.extend({ has: function( target ) { var targets = jQuery( target, this ), l = targets.length; return this.filter(function() { var i = 0; for ( ; i < l; i++ ) { if ( jQuery.contains( this, targets[i] ) ) { return true; } } }); }, closest: function( selectors, context ) { var cur, i = 0, l = this.length, matched = [], pos = rneedsContext.test( selectors ) || typeof selectors !== "string" ? jQuery( selectors, context || this.context ) : 0; for ( ; i < l; i++ ) { for ( cur = this[i]; cur && cur !== context; cur = cur.parentNode ) { // Always skip document fragments if ( cur.nodeType < 11 && (pos ? pos.index(cur) > -1 : // Don't pass non-elements to Sizzle cur.nodeType === 1 && jQuery.find.matchesSelector(cur, selectors)) ) { matched.push( cur ); break; } } } return this.pushStack( matched.length > 1 ? jQuery.unique( matched ) : matched ); }, // Determine the position of an element within // the matched set of elements index: function( elem ) { // No argument, return index in parent if ( !elem ) { return ( this[ 0 ] && this[ 0 ].parentNode ) ? this.first().prevAll().length : -1; } // index in selector if ( typeof elem === "string" ) { return indexOf.call( jQuery( elem ), this[ 0 ] ); } // Locate the position of the desired element return indexOf.call( this, // If it receives a jQuery object, the first element is used elem.jquery ? elem[ 0 ] : elem ); }, add: function( selector, context ) { return this.pushStack( jQuery.unique( jQuery.merge( this.get(), jQuery( selector, context ) ) ) ); }, addBack: function( selector ) { return this.add( selector == null ? this.prevObject : this.prevObject.filter(selector) ); } }); function sibling( cur, dir ) { while ( (cur = cur[dir]) && cur.nodeType !== 1 ) {} return cur; } jQuery.each({ parent: function( elem ) { var parent = elem.parentNode; return parent && parent.nodeType !== 11 ? parent : null; }, parents: function( elem ) { return jQuery.dir( elem, "parentNode" ); }, parentsUntil: function( elem, i, until ) { return jQuery.dir( elem, "parentNode", until ); }, next: function( elem ) { return sibling( elem, "nextSibling" ); }, prev: function( elem ) { return sibling( elem, "previousSibling" ); }, nextAll: function( elem ) { return jQuery.dir( elem, "nextSibling" ); }, prevAll: function( elem ) { return jQuery.dir( elem, "previousSibling" ); }, nextUntil: function( elem, i, until ) { return jQuery.dir( elem, "nextSibling", until ); }, prevUntil: function( elem, i, until ) { return jQuery.dir( elem, "previousSibling", until ); }, siblings: function( elem ) { return jQuery.sibling( ( elem.parentNode || {} ).firstChild, elem ); }, children: function( elem ) { return jQuery.sibling( elem.firstChild ); }, contents: function( elem ) { return elem.contentDocument || jQuery.merge( [], elem.childNodes ); } }, function( name, fn ) { jQuery.fn[ name ] = function( until, selector ) { var matched = jQuery.map( this, fn, until ); if ( name.slice( -5 ) !== "Until" ) { selector = until; } if ( selector && typeof selector === "string" ) { matched = jQuery.filter( selector, matched ); } if ( this.length > 1 ) { // Remove duplicates if ( !guaranteedUnique[ name ] ) { jQuery.unique( matched ); } // Reverse order for parents* and prev-derivatives if ( rparentsprev.test( name ) ) { matched.reverse(); } } return this.pushStack( matched ); }; }); var rnotwhite = (/\S+/g); // String to Object options format cache var optionsCache = {}; // Convert String-formatted options into Object-formatted ones and store in cache function createOptions( options ) { var object = optionsCache[ options ] = {}; jQuery.each( options.match( rnotwhite ) || [], function( _, flag ) { object[ flag ] = true; }); return object; } /* * Create a callback list using the following parameters: * * options: an optional list of space-separated options that will change how * the callback list behaves or a more traditional option object * * By default a callback list will act like an event callback list and can be * "fired" multiple times. * * Possible options: * * once: will ensure the callback list can only be fired once (like a Deferred) * * memory: will keep track of previous values and will call any callback added * after the list has been fired right away with the latest "memorized" * values (like a Deferred) * * unique: will ensure a callback can only be added once (no duplicate in the list) * * stopOnFalse: interrupt callings when a callback returns false * */ jQuery.Callbacks = function( options ) { // Convert options from String-formatted to Object-formatted if needed // (we check in cache first) options = typeof options === "string" ? ( optionsCache[ options ] || createOptions( options ) ) : jQuery.extend( {}, options ); var // Last fire value (for non-forgettable lists) memory, // Flag to know if list was already fired fired, // Flag to know if list is currently firing firing, // First callback to fire (used internally by add and fireWith) firingStart, // End of the loop when firing firingLength, // Index of currently firing callback (modified by remove if needed) firingIndex, // Actual callback list list = [], // Stack of fire calls for repeatable lists stack = !options.once && [], // Fire callbacks fire = function( data ) { memory = options.memory && data; fired = true; firingIndex = firingStart || 0; firingStart = 0; firingLength = list.length; firing = true; for ( ; list && firingIndex < firingLength; firingIndex++ ) { if ( list[ firingIndex ].apply( data[ 0 ], data[ 1 ] ) === false && options.stopOnFalse ) { memory = false; // To prevent further calls using add break; } } firing = false; if ( list ) { if ( stack ) { if ( stack.length ) { fire( stack.shift() ); } } else if ( memory ) { list = []; } else { self.disable(); } } }, // Actual Callbacks object self = { // Add a callback or a collection of callbacks to the list add: function() { if ( list ) { // First, we save the current length var start = list.length; (function add( args ) { jQuery.each( args, function( _, arg ) { var type = jQuery.type( arg ); if ( type === "function" ) { if ( !options.unique || !self.has( arg ) ) { list.push( arg ); } } else if ( arg && arg.length && type !== "string" ) { // Inspect recursively add( arg ); } }); })( arguments ); // Do we need to add the callbacks to the // current firing batch? if ( firing ) { firingLength = list.length; // With memory, if we're not firing then // we should call right away } else if ( memory ) { firingStart = start; fire( memory ); } } return this; }, // Remove a callback from the list remove: function() { if ( list ) { jQuery.each( arguments, function( _, arg ) { var index; while ( ( index = jQuery.inArray( arg, list, index ) ) > -1 ) { list.splice( index, 1 ); // Handle firing indexes if ( firing ) { if ( index <= firingLength ) { firingLength--; } if ( index <= firingIndex ) { firingIndex--; } } } }); } return this; }, // Check if a given callback is in the list. // If no argument is given, return whether or not list has callbacks attached. has: function( fn ) { return fn ? jQuery.inArray( fn, list ) > -1 : !!( list && list.length ); }, // Remove all callbacks from the list empty: function() { list = []; firingLength = 0; return this; }, // Have the list do nothing anymore disable: function() { list = stack = memory = undefined; return this; }, // Is it disabled? disabled: function() { return !list; }, // Lock the list in its current state lock: function() { stack = undefined; if ( !memory ) { self.disable(); } return this; }, // Is it locked? locked: function() { return !stack; }, // Call all callbacks with the given context and arguments fireWith: function( context, args ) { if ( list && ( !fired || stack ) ) { args = args || []; args = [ context, args.slice ? args.slice() : args ]; if ( firing ) { stack.push( args ); } else { fire( args ); } } return this; }, // Call all the callbacks with the given arguments fire: function() { self.fireWith( this, arguments ); return this; }, // To know if the callbacks have already been called at least once fired: function() { return !!fired; } }; return self; }; jQuery.extend({ Deferred: function( func ) { var tuples = [ // action, add listener, listener list, final state [ "resolve", "done", jQuery.Callbacks("once memory"), "resolved" ], [ "reject", "fail", jQuery.Callbacks("once memory"), "rejected" ], [ "notify", "progress", jQuery.Callbacks("memory") ] ], state = "pending", promise = { state: function() { return state; }, always: function() { deferred.done( arguments ).fail( arguments ); return this; }, then: function( /* fnDone, fnFail, fnProgress */ ) { var fns = arguments; return jQuery.Deferred(function( newDefer ) { jQuery.each( tuples, function( i, tuple ) { var fn = jQuery.isFunction( fns[ i ] ) && fns[ i ]; // deferred[ done | fail | progress ] for forwarding actions to newDefer deferred[ tuple[1] ](function() { var returned = fn && fn.apply( this, arguments ); if ( returned && jQuery.isFunction( returned.promise ) ) { returned.promise() .done( newDefer.resolve ) .fail( newDefer.reject ) .progress( newDefer.notify ); } else { newDefer[ tuple[ 0 ] + "With" ]( this === promise ? newDefer.promise() : this, fn ? [ returned ] : arguments ); } }); }); fns = null; }).promise(); }, // Get a promise for this deferred // If obj is provided, the promise aspect is added to the object promise: function( obj ) { return obj != null ? jQuery.extend( obj, promise ) : promise; } }, deferred = {}; // Keep pipe for back-compat promise.pipe = promise.then; // Add list-specific methods jQuery.each( tuples, function( i, tuple ) { var list = tuple[ 2 ], stateString = tuple[ 3 ]; // promise[ done | fail | progress ] = list.add promise[ tuple[1] ] = list.add; // Handle state if ( stateString ) { list.add(function() { // state = [ resolved | rejected ] state = stateString; // [ reject_list | resolve_list ].disable; progress_list.lock }, tuples[ i ^ 1 ][ 2 ].disable, tuples[ 2 ][ 2 ].lock ); } // deferred[ resolve | reject | notify ] deferred[ tuple[0] ] = function() { deferred[ tuple[0] + "With" ]( this === deferred ? promise : this, arguments ); return this; }; deferred[ tuple[0] + "With" ] = list.fireWith; }); // Make the deferred a promise promise.promise( deferred ); // Call given func if any if ( func ) { func.call( deferred, deferred ); } // All done! return deferred; }, // Deferred helper when: function( subordinate /* , ..., subordinateN */ ) { var i = 0, resolveValues = slice.call( arguments ), length = resolveValues.length, // the count of uncompleted subordinates remaining = length !== 1 || ( subordinate && jQuery.isFunction( subordinate.promise ) ) ? length : 0, // the master Deferred. If resolveValues consist of only a single Deferred, just use that. deferred = remaining === 1 ? subordinate : jQuery.Deferred(), // Update function for both resolve and progress values updateFunc = function( i, contexts, values ) { return function( value ) { contexts[ i ] = this; values[ i ] = arguments.length > 1 ? slice.call( arguments ) : value; if ( values === progressValues ) { deferred.notifyWith( contexts, values ); } else if ( !( --remaining ) ) { deferred.resolveWith( contexts, values ); } }; }, progressValues, progressContexts, resolveContexts; // add listeners to Deferred subordinates; treat others as resolved if ( length > 1 ) { progressValues = new Array( length ); progressContexts = new Array( length ); resolveContexts = new Array( length ); for ( ; i < length; i++ ) { if ( resolveValues[ i ] && jQuery.isFunction( resolveValues[ i ].promise ) ) { resolveValues[ i ].promise() .done( updateFunc( i, resolveContexts, resolveValues ) ) .fail( deferred.reject ) .progress( updateFunc( i, progressContexts, progressValues ) ); } else { --remaining; } } } // if we're not waiting on anything, resolve the master if ( !remaining ) { deferred.resolveWith( resolveContexts, resolveValues ); } return deferred.promise(); } }); // The deferred used on DOM ready var readyList; jQuery.fn.ready = function( fn ) { // Add the callback jQuery.ready.promise().done( fn ); return this; }; jQuery.extend({ // Is the DOM ready to be used? Set to true once it occurs. isReady: false, // A counter to track how many items to wait for before // the ready event fires. See #6781 readyWait: 1, // Hold (or release) the ready event holdReady: function( hold ) { if ( hold ) { jQuery.readyWait++; } else { jQuery.ready( true ); } }, // Handle when the DOM is ready ready: function( wait ) { // Abort if there are pending holds or we're already ready if ( wait === true ? --jQuery.readyWait : jQuery.isReady ) { return; } // Remember that the DOM is ready jQuery.isReady = true; // If a normal DOM Ready event fired, decrement, and wait if need be if ( wait !== true && --jQuery.readyWait > 0 ) { return; } // If there are functions bound, to execute readyList.resolveWith( document, [ jQuery ] ); // Trigger any bound ready events if ( jQuery.fn.triggerHandler ) { jQuery( document ).triggerHandler( "ready" ); jQuery( document ).off( "ready" ); } } }); /** * The ready event handler and self cleanup method */ function completed() { document.removeEventListener( "DOMContentLoaded", completed, false ); window.removeEventListener( "load", completed, false ); jQuery.ready(); } jQuery.ready.promise = function( obj ) { if ( !readyList ) { readyList = jQuery.Deferred(); // Catch cases where $(document).ready() is called after the browser event has already occurred. // we once tried to use readyState "interactive" here, but it caused issues like the one // discovered by ChrisS here: http://bugs.jquery.com/ticket/12282#comment:15 if ( document.readyState === "complete" ) { // Handle it asynchronously to allow scripts the opportunity to delay ready setTimeout( jQuery.ready ); } else { // Use the handy event callback document.addEventListener( "DOMContentLoaded", completed, false ); // A fallback to window.onload, that will always work window.addEventListener( "load", completed, false ); } } return readyList.promise( obj ); }; // Kick off the DOM ready check even if the user does not jQuery.ready.promise(); // Multifunctional method to get and set values of a collection // The value/s can optionally be executed if it's a function var access = jQuery.access = function( elems, fn, key, value, chainable, emptyGet, raw ) { var i = 0, len = elems.length, bulk = key == null; // Sets many values if ( jQuery.type( key ) === "object" ) { chainable = true; for ( i in key ) { jQuery.access( elems, fn, i, key[i], true, emptyGet, raw ); } // Sets one value } else if ( value !== undefined ) { chainable = true; if ( !jQuery.isFunction( value ) ) { raw = true; } if ( bulk ) { // Bulk operations run against the entire set if ( raw ) { fn.call( elems, value ); fn = null; // ...except when executing function values } else { bulk = fn; fn = function( elem, key, value ) { return bulk.call( jQuery( elem ), value ); }; } } if ( fn ) { for ( ; i < len; i++ ) { fn( elems[i], key, raw ? value : value.call( elems[i], i, fn( elems[i], key ) ) ); } } } return chainable ? elems : // Gets bulk ? fn.call( elems ) : len ? fn( elems[0], key ) : emptyGet; }; /** * Determines whether an object can have data */ jQuery.acceptData = function( owner ) { // Accepts only: // - Node // - Node.ELEMENT_NODE // - Node.DOCUMENT_NODE // - Object // - Any /* jshint -W018 */ return owner.nodeType === 1 || owner.nodeType === 9 || !( +owner.nodeType ); }; function Data() { // Support: Android < 4, // Old WebKit does not have Object.preventExtensions/freeze method, // return new empty object instead with no [[set]] accessor Object.defineProperty( this.cache = {}, 0, { get: function() { return {}; } }); this.expando = jQuery.expando + Math.random(); } Data.uid = 1; Data.accepts = jQuery.acceptData; Data.prototype = { key: function( owner ) { // We can accept data for non-element nodes in modern browsers, // but we should not, see #8335. // Always return the key for a frozen object. if ( !Data.accepts( owner ) ) { return 0; } var descriptor = {}, // Check if the owner object already has a cache key unlock = owner[ this.expando ]; // If not, create one if ( !unlock ) { unlock = Data.uid++; // Secure it in a non-enumerable, non-writable property try { descriptor[ this.expando ] = { value: unlock }; Object.defineProperties( owner, descriptor ); // Support: Android < 4 // Fallback to a less secure definition } catch ( e ) { descriptor[ this.expando ] = unlock; jQuery.extend( owner, descriptor ); } } // Ensure the cache object if ( !this.cache[ unlock ] ) { this.cache[ unlock ] = {}; } return unlock; }, set: function( owner, data, value ) { var prop, // There may be an unlock assigned to this node, // if there is no entry for this "owner", create one inline // and set the unlock as though an owner entry had always existed unlock = this.key( owner ), cache = this.cache[ unlock ]; // Handle: [ owner, key, value ] args if ( typeof data === "string" ) { cache[ data ] = value; // Handle: [ owner, { properties } ] args } else { // Fresh assignments by object are shallow copied if ( jQuery.isEmptyObject( cache ) ) { jQuery.extend( this.cache[ unlock ], data ); // Otherwise, copy the properties one-by-one to the cache object } else { for ( prop in data ) { cache[ prop ] = data[ prop ]; } } } return cache; }, get: function( owner, key ) { // Either a valid cache is found, or will be created. // New caches will be created and the unlock returned, // allowing direct access to the newly created // empty data object. A valid owner object must be provided. var cache = this.cache[ this.key( owner ) ]; return key === undefined ? cache : cache[ key ]; }, access: function( owner, key, value ) { var stored; // In cases where either: // // 1. No key was specified // 2. A string key was specified, but no value provided // // Take the "read" path and allow the get method to determine // which value to return, respectively either: // // 1. The entire cache object // 2. The data stored at the key // if ( key === undefined || ((key && typeof key === "string") && value === undefined) ) { stored = this.get( owner, key ); return stored !== undefined ? stored : this.get( owner, jQuery.camelCase(key) ); } // [*]When the key is not a string, or both a key and value // are specified, set or extend (existing objects) with either: // // 1. An object of properties // 2. A key and value // this.set( owner, key, value ); // Since the "set" path can have two possible entry points // return the expected data based on which path was taken[*] return value !== undefined ? value : key; }, remove: function( owner, key ) { var i, name, camel, unlock = this.key( owner ), cache = this.cache[ unlock ]; if ( key === undefined ) { this.cache[ unlock ] = {}; } else { // Support array or space separated string of keys if ( jQuery.isArray( key ) ) { // If "name" is an array of keys... // When data is initially created, via ("key", "val") signature, // keys will be converted to camelCase. // Since there is no way to tell _how_ a key was added, remove // both plain key and camelCase key. #12786 // This will only penalize the array argument path. name = key.concat( key.map( jQuery.camelCase ) ); } else { camel = jQuery.camelCase( key ); // Try the string as a key before any manipulation if ( key in cache ) { name = [ key, camel ]; } else { // If a key with the spaces exists, use it. // Otherwise, create an array by matching non-whitespace name = camel; name = name in cache ? [ name ] : ( name.match( rnotwhite ) || [] ); } } i = name.length; while ( i-- ) { delete cache[ name[ i ] ]; } } }, hasData: function( owner ) { return !jQuery.isEmptyObject( this.cache[ owner[ this.expando ] ] || {} ); }, discard: function( owner ) { if ( owner[ this.expando ] ) { delete this.cache[ owner[ this.expando ] ]; } } }; var data_priv = new Data(); var data_user = new Data(); /* Implementation Summary 1. Enforce API surface and semantic compatibility with 1.9.x branch 2. Improve the module's maintainability by reducing the storage paths to a single mechanism. 3. Use the same single mechanism to support "private" and "user" data. 4. _Never_ expose "private" data to user code (TODO: Drop _data, _removeData) 5. Avoid exposing implementation details on user objects (eg. expando properties) 6. Provide a clear path for implementation upgrade to WeakMap in 2014 */ var rbrace = /^(?:\{[\w\W]*\}|\[[\w\W]*\])$/, rmultiDash = /([A-Z])/g; function dataAttr( elem, key, data ) { var name; // If nothing was found internally, try to fetch any // data from the HTML5 data-* attribute if ( data === undefined && elem.nodeType === 1 ) { name = "data-" + key.replace( rmultiDash, "-$1" ).toLowerCase(); data = elem.getAttribute( name ); if ( typeof data === "string" ) { try { data = data === "true" ? true : data === "false" ? false : data === "null" ? null : // Only convert to a number if it doesn't change the string +data + "" === data ? +data : rbrace.test( data ) ? jQuery.parseJSON( data ) : data; } catch( e ) {} // Make sure we set the data so it isn't changed later data_user.set( elem, key, data ); } else { data = undefined; } } return data; } jQuery.extend({ hasData: function( elem ) { return data_user.hasData( elem ) || data_priv.hasData( elem ); }, data: function( elem, name, data ) { return data_user.access( elem, name, data ); }, removeData: function( elem, name ) { data_user.remove( elem, name ); }, // TODO: Now that all calls to _data and _removeData have been replaced // with direct calls to data_priv methods, these can be deprecated. _data: function( elem, name, data ) { return data_priv.access( elem, name, data ); }, _removeData: function( elem, name ) { data_priv.remove( elem, name ); } }); jQuery.fn.extend({ data: function( key, value ) { var i, name, data, elem = this[ 0 ], attrs = elem && elem.attributes; // Gets all values if ( key === undefined ) { if ( this.length ) { data = data_user.get( elem ); if ( elem.nodeType === 1 && !data_priv.get( elem, "hasDataAttrs" ) ) { i = attrs.length; while ( i-- ) { // Support: IE11+ // The attrs elements can be null (#14894) if ( attrs[ i ] ) { name = attrs[ i ].name; if ( name.indexOf( "data-" ) === 0 ) { name = jQuery.camelCase( name.slice(5) ); dataAttr( elem, name, data[ name ] ); } } } data_priv.set( elem, "hasDataAttrs", true ); } } return data; } // Sets multiple values if ( typeof key === "object" ) { return this.each(function() { data_user.set( this, key ); }); } return access( this, function( value ) { var data, camelKey = jQuery.camelCase( key ); // The calling jQuery object (element matches) is not empty // (and therefore has an element appears at this[ 0 ]) and the // `value` parameter was not undefined. An empty jQuery object // will result in `undefined` for elem = this[ 0 ] which will // throw an exception if an attempt to read a data cache is made. if ( elem && value === undefined ) { // Attempt to get data from the cache // with the key as-is data = data_user.get( elem, key ); if ( data !== undefined ) { return data; } // Attempt to get data from the cache // with the key camelized data = data_user.get( elem, camelKey ); if ( data !== undefined ) { return data; } // Attempt to "discover" the data in // HTML5 custom data-* attrs data = dataAttr( elem, camelKey, undefined ); if ( data !== undefined ) { return data; } // We tried really hard, but the data doesn't exist. return; } // Set the data... this.each(function() { // First, attempt to store a copy or reference of any // data that might've been store with a camelCased key. var data = data_user.get( this, camelKey ); // For HTML5 data-* attribute interop, we have to // store property names with dashes in a camelCase form. // This might not apply to all properties...* data_user.set( this, camelKey, value ); // *... In the case of properties that might _actually_ // have dashes, we need to also store a copy of that // unchanged property. if ( key.indexOf("-") !== -1 && data !== undefined ) { data_user.set( this, key, value ); } }); }, null, value, arguments.length > 1, null, true ); }, removeData: function( key ) { return this.each(function() { data_user.remove( this, key ); }); } }); jQuery.extend({ queue: function( elem, type, data ) { var queue; if ( elem ) { type = ( type || "fx" ) + "queue"; queue = data_priv.get( elem, type ); // Speed up dequeue by getting out quickly if this is just a lookup if ( data ) { if ( !queue || jQuery.isArray( data ) ) { queue = data_priv.access( elem, type, jQuery.makeArray(data) ); } else { queue.push( data ); } } return queue || []; } }, dequeue: function( elem, type ) { type = type || "fx"; var queue = jQuery.queue( elem, type ), startLength = queue.length, fn = queue.shift(), hooks = jQuery._queueHooks( elem, type ), next = function() { jQuery.dequeue( elem, type ); }; // If the fx queue is dequeued, always remove the progress sentinel if ( fn === "inprogress" ) { fn = queue.shift(); startLength--; } if ( fn ) { // Add a progress sentinel to prevent the fx queue from being // automatically dequeued if ( type === "fx" ) { queue.unshift( "inprogress" ); } // clear up the last queue stop function delete hooks.stop; fn.call( elem, next, hooks ); } if ( !startLength && hooks ) { hooks.empty.fire(); } }, // not intended for public consumption - generates a queueHooks object, or returns the current one _queueHooks: function( elem, type ) { var key = type + "queueHooks"; return data_priv.get( elem, key ) || data_priv.access( elem, key, { empty: jQuery.Callbacks("once memory").add(function() { data_priv.remove( elem, [ type + "queue", key ] ); }) }); } }); jQuery.fn.extend({ queue: function( type, data ) { var setter = 2; if ( typeof type !== "string" ) { data = type; type = "fx"; setter--; } if ( arguments.length < setter ) { return jQuery.queue( this[0], type ); } return data === undefined ? this : this.each(function() { var queue = jQuery.queue( this, type, data ); // ensure a hooks for this queue jQuery._queueHooks( this, type ); if ( type === "fx" && queue[0] !== "inprogress" ) { jQuery.dequeue( this, type ); } }); }, dequeue: function( type ) { return this.each(function() { jQuery.dequeue( this, type ); }); }, clearQueue: function( type ) { return this.queue( type || "fx", [] ); }, // Get a promise resolved when queues of a certain type // are emptied (fx is the type by default) promise: function( type, obj ) { var tmp, count = 1, defer = jQuery.Deferred(), elements = this, i = this.length, resolve = function() { if ( !( --count ) ) { defer.resolveWith( elements, [ elements ] ); } }; if ( typeof type !== "string" ) { obj = type; type = undefined; } type = type || "fx"; while ( i-- ) { tmp = data_priv.get( elements[ i ], type + "queueHooks" ); if ( tmp && tmp.empty ) { count++; tmp.empty.add( resolve ); } } resolve(); return defer.promise( obj ); } }); var pnum = (/[+-]?(?:\d*\.|)\d+(?:[eE][+-]?\d+|)/).source; var cssExpand = [ "Top", "Right", "Bottom", "Left" ]; var isHidden = function( elem, el ) { // isHidden might be called from jQuery#filter function; // in that case, element will be second argument elem = el || elem; return jQuery.css( elem, "display" ) === "none" || !jQuery.contains( elem.ownerDocument, elem ); }; var rcheckableType = (/^(?:checkbox|radio)$/i); (function() { var fragment = document.createDocumentFragment(), div = fragment.appendChild( document.createElement( "div" ) ), input = document.createElement( "input" ); // #11217 - WebKit loses check when the name is after the checked attribute // Support: Windows Web Apps (WWA) // `name` and `type` need .setAttribute for WWA input.setAttribute( "type", "radio" ); input.setAttribute( "checked", "checked" ); input.setAttribute( "name", "t" ); div.appendChild( input ); // Support: Safari 5.1, iOS 5.1, Android 4.x, Android 2.3 // old WebKit doesn't clone checked state correctly in fragments support.checkClone = div.cloneNode( true ).cloneNode( true ).lastChild.checked; // Make sure textarea (and checkbox) defaultValue is properly cloned // Support: IE9-IE11+ div.innerHTML = ""; support.noCloneChecked = !!div.cloneNode( true ).lastChild.defaultValue; })(); var strundefined = typeof undefined; support.focusinBubbles = "onfocusin" in window; var rkeyEvent = /^key/, rmouseEvent = /^(?:mouse|pointer|contextmenu)|click/, rfocusMorph = /^(?:focusinfocus|focusoutblur)$/, rtypenamespace = /^([^.]*)(?:\.(.+)|)$/; function returnTrue() { return true; } function returnFalse() { return false; } function safeActiveElement() { try { return document.activeElement; } catch ( err ) { } } /* * Helper functions for managing events -- not part of the public interface. * Props to Dean Edwards' addEvent library for many of the ideas. */ jQuery.event = { global: {}, add: function( elem, types, handler, data, selector ) { var handleObjIn, eventHandle, tmp, events, t, handleObj, special, handlers, type, namespaces, origType, elemData = data_priv.get( elem ); // Don't attach events to noData or text/comment nodes (but allow plain objects) if ( !elemData ) { return; } // Caller can pass in an object of custom data in lieu of the handler if ( handler.handler ) { handleObjIn = handler; handler = handleObjIn.handler; selector = handleObjIn.selector; } // Make sure that the handler has a unique ID, used to find/remove it later if ( !handler.guid ) { handler.guid = jQuery.guid++; } // Init the element's event structure and main handler, if this is the first if ( !(events = elemData.events) ) { events = elemData.events = {}; } if ( !(eventHandle = elemData.handle) ) { eventHandle = elemData.handle = function( e ) { // Discard the second event of a jQuery.event.trigger() and // when an event is called after a page has unloaded return typeof jQuery !== strundefined && jQuery.event.triggered !== e.type ? jQuery.event.dispatch.apply( elem, arguments ) : undefined; }; } // Handle multiple events separated by a space types = ( types || "" ).match( rnotwhite ) || [ "" ]; t = types.length; while ( t-- ) { tmp = rtypenamespace.exec( types[t] ) || []; type = origType = tmp[1]; namespaces = ( tmp[2] || "" ).split( "." ).sort(); // There *must* be a type, no attaching namespace-only handlers if ( !type ) { continue; } // If event changes its type, use the special event handlers for the changed type special = jQuery.event.special[ type ] || {}; // If selector defined, determine special event api type, otherwise given type type = ( selector ? special.delegateType : special.bindType ) || type; // Update special based on newly reset type special = jQuery.event.special[ type ] || {}; // handleObj is passed to all event handlers handleObj = jQuery.extend({ type: type, origType: origType, data: data, handler: handler, guid: handler.guid, selector: selector, needsContext: selector && jQuery.expr.match.needsContext.test( selector ), namespace: namespaces.join(".") }, handleObjIn ); // Init the event handler queue if we're the first if ( !(handlers = events[ type ]) ) { handlers = events[ type ] = []; handlers.delegateCount = 0; // Only use addEventListener if the special events handler returns false if ( !special.setup || special.setup.call( elem, data, namespaces, eventHandle ) === false ) { if ( elem.addEventListener ) { elem.addEventListener( type, eventHandle, false ); } } } if ( special.add ) { special.add.call( elem, handleObj ); if ( !handleObj.handler.guid ) { handleObj.handler.guid = handler.guid; } } // Add to the element's handler list, delegates in front if ( selector ) { handlers.splice( handlers.delegateCount++, 0, handleObj ); } else { handlers.push( handleObj ); } // Keep track of which events have ever been used, for event optimization jQuery.event.global[ type ] = true; } }, // Detach an event or set of events from an element remove: function( elem, types, handler, selector, mappedTypes ) { var j, origCount, tmp, events, t, handleObj, special, handlers, type, namespaces, origType, elemData = data_priv.hasData( elem ) && data_priv.get( elem ); if ( !elemData || !(events = elemData.events) ) { return; } // Once for each type.namespace in types; type may be omitted types = ( types || "" ).match( rnotwhite ) || [ "" ]; t = types.length; while ( t-- ) { tmp = rtypenamespace.exec( types[t] ) || []; type = origType = tmp[1]; namespaces = ( tmp[2] || "" ).split( "." ).sort(); // Unbind all events (on this namespace, if provided) for the element if ( !type ) { for ( type in events ) { jQuery.event.remove( elem, type + types[ t ], handler, selector, true ); } continue; } special = jQuery.event.special[ type ] || {}; type = ( selector ? special.delegateType : special.bindType ) || type; handlers = events[ type ] || []; tmp = tmp[2] && new RegExp( "(^|\\.)" + namespaces.join("\\.(?:.*\\.|)") + "(\\.|$)" ); // Remove matching events origCount = j = handlers.length; while ( j-- ) { handleObj = handlers[ j ]; if ( ( mappedTypes || origType === handleObj.origType ) && ( !handler || handler.guid === handleObj.guid ) && ( !tmp || tmp.test( handleObj.namespace ) ) && ( !selector || selector === handleObj.selector || selector === "**" && handleObj.selector ) ) { handlers.splice( j, 1 ); if ( handleObj.selector ) { handlers.delegateCount--; } if ( special.remove ) { special.remove.call( elem, handleObj ); } } } // Remove generic event handler if we removed something and no more handlers exist // (avoids potential for endless recursion during removal of special event handlers) if ( origCount && !handlers.length ) { if ( !special.teardown || special.teardown.call( elem, namespaces, elemData.handle ) === false ) { jQuery.removeEvent( elem, type, elemData.handle ); } delete events[ type ]; } } // Remove the expando if it's no longer used if ( jQuery.isEmptyObject( events ) ) { delete elemData.handle; data_priv.remove( elem, "events" ); } }, trigger: function( event, data, elem, onlyHandlers ) { var i, cur, tmp, bubbleType, ontype, handle, special, eventPath = [ elem || document ], type = hasOwn.call( event, "type" ) ? event.type : event, namespaces = hasOwn.call( event, "namespace" ) ? event.namespace.split(".") : []; cur = tmp = elem = elem || document; // Don't do events on text and comment nodes if ( elem.nodeType === 3 || elem.nodeType === 8 ) { return; } // focus/blur morphs to focusin/out; ensure we're not firing them right now if ( rfocusMorph.test( type + jQuery.event.triggered ) ) { return; } if ( type.indexOf(".") >= 0 ) { // Namespaced trigger; create a regexp to match event type in handle() namespaces = type.split("."); type = namespaces.shift(); namespaces.sort(); } ontype = type.indexOf(":") < 0 && "on" + type; // Caller can pass in a jQuery.Event object, Object, or just an event type string event = event[ jQuery.expando ] ? event : new jQuery.Event( type, typeof event === "object" && event ); // Trigger bitmask: & 1 for native handlers; & 2 for jQuery (always true) event.isTrigger = onlyHandlers ? 2 : 3; event.namespace = namespaces.join("."); event.namespace_re = event.namespace ? new RegExp( "(^|\\.)" + namespaces.join("\\.(?:.*\\.|)") + "(\\.|$)" ) : null; // Clean up the event in case it is being reused event.result = undefined; if ( !event.target ) { event.target = elem; } // Clone any incoming data and prepend the event, creating the handler arg list data = data == null ? [ event ] : jQuery.makeArray( data, [ event ] ); // Allow special events to draw outside the lines special = jQuery.event.special[ type ] || {}; if ( !onlyHandlers && special.trigger && special.trigger.apply( elem, data ) === false ) { return; } // Determine event propagation path in advance, per W3C events spec (#9951) // Bubble up to document, then to window; watch for a global ownerDocument var (#9724) if ( !onlyHandlers && !special.noBubble && !jQuery.isWindow( elem ) ) { bubbleType = special.delegateType || type; if ( !rfocusMorph.test( bubbleType + type ) ) { cur = cur.parentNode; } for ( ; cur; cur = cur.parentNode ) { eventPath.push( cur ); tmp = cur; } // Only add window if we got to document (e.g., not plain obj or detached DOM) if ( tmp === (elem.ownerDocument || document) ) { eventPath.push( tmp.defaultView || tmp.parentWindow || window ); } } // Fire handlers on the event path i = 0; while ( (cur = eventPath[i++]) && !event.isPropagationStopped() ) { event.type = i > 1 ? bubbleType : special.bindType || type; // jQuery handler handle = ( data_priv.get( cur, "events" ) || {} )[ event.type ] && data_priv.get( cur, "handle" ); if ( handle ) { handle.apply( cur, data ); } // Native handler handle = ontype && cur[ ontype ]; if ( handle && handle.apply && jQuery.acceptData( cur ) ) { event.result = handle.apply( cur, data ); if ( event.result === false ) { event.preventDefault(); } } } event.type = type; // If nobody prevented the default action, do it now if ( !onlyHandlers && !event.isDefaultPrevented() ) { if ( (!special._default || special._default.apply( eventPath.pop(), data ) === false) && jQuery.acceptData( elem ) ) { // Call a native DOM method on the target with the same name name as the event. // Don't do default actions on window, that's where global variables be (#6170) if ( ontype && jQuery.isFunction( elem[ type ] ) && !jQuery.isWindow( elem ) ) { // Don't re-trigger an onFOO event when we call its FOO() method tmp = elem[ ontype ]; if ( tmp ) { elem[ ontype ] = null; } // Prevent re-triggering of the same event, since we already bubbled it above jQuery.event.triggered = type; elem[ type ](); jQuery.event.triggered = undefined; if ( tmp ) { elem[ ontype ] = tmp; } } } } return event.result; }, dispatch: function( event ) { // Make a writable jQuery.Event from the native event object event = jQuery.event.fix( event ); var i, j, ret, matched, handleObj, handlerQueue = [], args = slice.call( arguments ), handlers = ( data_priv.get( this, "events" ) || {} )[ event.type ] || [], special = jQuery.event.special[ event.type ] || {}; // Use the fix-ed jQuery.Event rather than the (read-only) native event args[0] = event; event.delegateTarget = this; // Call the preDispatch hook for the mapped type, and let it bail if desired if ( special.preDispatch && special.preDispatch.call( this, event ) === false ) { return; } // Determine handlers handlerQueue = jQuery.event.handlers.call( this, event, handlers ); // Run delegates first; they may want to stop propagation beneath us i = 0; while ( (matched = handlerQueue[ i++ ]) && !event.isPropagationStopped() ) { event.currentTarget = matched.elem; j = 0; while ( (handleObj = matched.handlers[ j++ ]) && !event.isImmediatePropagationStopped() ) { // Triggered event must either 1) have no namespace, or // 2) have namespace(s) a subset or equal to those in the bound event (both can have no namespace). if ( !event.namespace_re || event.namespace_re.test( handleObj.namespace ) ) { event.handleObj = handleObj; event.data = handleObj.data; ret = ( (jQuery.event.special[ handleObj.origType ] || {}).handle || handleObj.handler ) .apply( matched.elem, args ); if ( ret !== undefined ) { if ( (event.result = ret) === false ) { event.preventDefault(); event.stopPropagation(); } } } } } // Call the postDispatch hook for the mapped type if ( special.postDispatch ) { special.postDispatch.call( this, event ); } return event.result; }, handlers: function( event, handlers ) { var i, matches, sel, handleObj, handlerQueue = [], delegateCount = handlers.delegateCount, cur = event.target; // Find delegate handlers // Black-hole SVG instance trees (#13180) // Avoid non-left-click bubbling in Firefox (#3861) if ( delegateCount && cur.nodeType && (!event.button || event.type !== "click") ) { for ( ; cur !== this; cur = cur.parentNode || this ) { // Don't process clicks on disabled elements (#6911, #8165, #11382, #11764) if ( cur.disabled !== true || event.type !== "click" ) { matches = []; for ( i = 0; i < delegateCount; i++ ) { handleObj = handlers[ i ]; // Don't conflict with Object.prototype properties (#13203) sel = handleObj.selector + " "; if ( matches[ sel ] === undefined ) { matches[ sel ] = handleObj.needsContext ? jQuery( sel, this ).index( cur ) >= 0 : jQuery.find( sel, this, null, [ cur ] ).length; } if ( matches[ sel ] ) { matches.push( handleObj ); } } if ( matches.length ) { handlerQueue.push({ elem: cur, handlers: matches }); } } } } // Add the remaining (directly-bound) handlers if ( delegateCount < handlers.length ) { handlerQueue.push({ elem: this, handlers: handlers.slice( delegateCount ) }); } return handlerQueue; }, // Includes some event props shared by KeyEvent and MouseEvent props: "altKey bubbles cancelable ctrlKey currentTarget eventPhase metaKey relatedTarget shiftKey target timeStamp view which".split(" "), fixHooks: {}, keyHooks: { props: "char charCode key keyCode".split(" "), filter: function( event, original ) { // Add which for key events if ( event.which == null ) { event.which = original.charCode != null ? original.charCode : original.keyCode; } return event; } }, mouseHooks: { props: "button buttons clientX clientY offsetX offsetY pageX pageY screenX screenY toElement".split(" "), filter: function( event, original ) { var eventDoc, doc, body, button = original.button; // Calculate pageX/Y if missing and clientX/Y available if ( event.pageX == null && original.clientX != null ) { eventDoc = event.target.ownerDocument || document; doc = eventDoc.documentElement; body = eventDoc.body; event.pageX = original.clientX + ( doc && doc.scrollLeft || body && body.scrollLeft || 0 ) - ( doc && doc.clientLeft || body && body.clientLeft || 0 ); event.pageY = original.clientY + ( doc && doc.scrollTop || body && body.scrollTop || 0 ) - ( doc && doc.clientTop || body && body.clientTop || 0 ); } // Add which for click: 1 === left; 2 === middle; 3 === right // Note: button is not normalized, so don't use it if ( !event.which && button !== undefined ) { event.which = ( button & 1 ? 1 : ( button & 2 ? 3 : ( button & 4 ? 2 : 0 ) ) ); } return event; } }, fix: function( event ) { if ( event[ jQuery.expando ] ) { return event; } // Create a writable copy of the event object and normalize some properties var i, prop, copy, type = event.type, originalEvent = event, fixHook = this.fixHooks[ type ]; if ( !fixHook ) { this.fixHooks[ type ] = fixHook = rmouseEvent.test( type ) ? this.mouseHooks : rkeyEvent.test( type ) ? this.keyHooks : {}; } copy = fixHook.props ? this.props.concat( fixHook.props ) : this.props; event = new jQuery.Event( originalEvent ); i = copy.length; while ( i-- ) { prop = copy[ i ]; event[ prop ] = originalEvent[ prop ]; } // Support: Cordova 2.5 (WebKit) (#13255) // All events should have a target; Cordova deviceready doesn't if ( !event.target ) { event.target = document; } // Support: Safari 6.0+, Chrome < 28 // Target should not be a text node (#504, #13143) if ( event.target.nodeType === 3 ) { event.target = event.target.parentNode; } return fixHook.filter ? fixHook.filter( event, originalEvent ) : event; }, special: { load: { // Prevent triggered image.load events from bubbling to window.load noBubble: true }, focus: { // Fire native event if possible so blur/focus sequence is correct trigger: function() { if ( this !== safeActiveElement() && this.focus ) { this.focus(); return false; } }, delegateType: "focusin" }, blur: { trigger: function() { if ( this === safeActiveElement() && this.blur ) { this.blur(); return false; } }, delegateType: "focusout" }, click: { // For checkbox, fire native event so checked state will be right trigger: function() { if ( this.type === "checkbox" && this.click && jQuery.nodeName( this, "input" ) ) { this.click(); return false; } }, // For cross-browser consistency, don't fire native .click() on links _default: function( event ) { return jQuery.nodeName( event.target, "a" ); } }, beforeunload: { postDispatch: function( event ) { // Support: Firefox 20+ // Firefox doesn't alert if the returnValue field is not set. if ( event.result !== undefined && event.originalEvent ) { event.originalEvent.returnValue = event.result; } } } }, simulate: function( type, elem, event, bubble ) { // Piggyback on a donor event to simulate a different one. // Fake originalEvent to avoid donor's stopPropagation, but if the // simulated event prevents default then we do the same on the donor. var e = jQuery.extend( new jQuery.Event(), event, { type: type, isSimulated: true, originalEvent: {} } ); if ( bubble ) { jQuery.event.trigger( e, null, elem ); } else { jQuery.event.dispatch.call( elem, e ); } if ( e.isDefaultPrevented() ) { event.preventDefault(); } } }; jQuery.removeEvent = function( elem, type, handle ) { if ( elem.removeEventListener ) { elem.removeEventListener( type, handle, false ); } }; jQuery.Event = function( src, props ) { // Allow instantiation without the 'new' keyword if ( !(this instanceof jQuery.Event) ) { return new jQuery.Event( src, props ); } // Event object if ( src && src.type ) { this.originalEvent = src; this.type = src.type; // Events bubbling up the document may have been marked as prevented // by a handler lower down the tree; reflect the correct value. this.isDefaultPrevented = src.defaultPrevented || src.defaultPrevented === undefined && // Support: Android < 4.0 src.returnValue === false ? returnTrue : returnFalse; // Event type } else { this.type = src; } // Put explicitly provided properties onto the event object if ( props ) { jQuery.extend( this, props ); } // Create a timestamp if incoming event doesn't have one this.timeStamp = src && src.timeStamp || jQuery.now(); // Mark it as fixed this[ jQuery.expando ] = true; }; // jQuery.Event is based on DOM3 Events as specified by the ECMAScript Language Binding // http://www.w3.org/TR/2003/WD-DOM-Level-3-Events-20030331/ecma-script-binding.html jQuery.Event.prototype = { isDefaultPrevented: returnFalse, isPropagationStopped: returnFalse, isImmediatePropagationStopped: returnFalse, preventDefault: function() { var e = this.originalEvent; this.isDefaultPrevented = returnTrue; if ( e && e.preventDefault ) { e.preventDefault(); } }, stopPropagation: function() { var e = this.originalEvent; this.isPropagationStopped = returnTrue; if ( e && e.stopPropagation ) { e.stopPropagation(); } }, stopImmediatePropagation: function() { var e = this.originalEvent; this.isImmediatePropagationStopped = returnTrue; if ( e && e.stopImmediatePropagation ) { e.stopImmediatePropagation(); } this.stopPropagation(); } }; // Create mouseenter/leave events using mouseover/out and event-time checks // Support: Chrome 15+ jQuery.each({ mouseenter: "mouseover", mouseleave: "mouseout", pointerenter: "pointerover", pointerleave: "pointerout" }, function( orig, fix ) { jQuery.event.special[ orig ] = { delegateType: fix, bindType: fix, handle: function( event ) { var ret, target = this, related = event.relatedTarget, handleObj = event.handleObj; // For mousenter/leave call the handler if related is outside the target. // NB: No relatedTarget if the mouse left/entered the browser window if ( !related || (related !== target && !jQuery.contains( target, related )) ) { event.type = handleObj.origType; ret = handleObj.handler.apply( this, arguments ); event.type = fix; } return ret; } }; }); // Create "bubbling" focus and blur events // Support: Firefox, Chrome, Safari if ( !support.focusinBubbles ) { jQuery.each({ focus: "focusin", blur: "focusout" }, function( orig, fix ) { // Attach a single capturing handler on the document while someone wants focusin/focusout var handler = function( event ) { jQuery.event.simulate( fix, event.target, jQuery.event.fix( event ), true ); }; jQuery.event.special[ fix ] = { setup: function() { var doc = this.ownerDocument || this, attaches = data_priv.access( doc, fix ); if ( !attaches ) { doc.addEventListener( orig, handler, true ); } data_priv.access( doc, fix, ( attaches || 0 ) + 1 ); }, teardown: function() { var doc = this.ownerDocument || this, attaches = data_priv.access( doc, fix ) - 1; if ( !attaches ) { doc.removeEventListener( orig, handler, true ); data_priv.remove( doc, fix ); } else { data_priv.access( doc, fix, attaches ); } } }; }); } jQuery.fn.extend({ on: function( types, selector, data, fn, /*INTERNAL*/ one ) { var origFn, type; // Types can be a map of types/handlers if ( typeof types === "object" ) { // ( types-Object, selector, data ) if ( typeof selector !== "string" ) { // ( types-Object, data ) data = data || selector; selector = undefined; } for ( type in types ) { this.on( type, selector, data, types[ type ], one ); } return this; } if ( data == null && fn == null ) { // ( types, fn ) fn = selector; data = selector = undefined; } else if ( fn == null ) { if ( typeof selector === "string" ) { // ( types, selector, fn ) fn = data; data = undefined; } else { // ( types, data, fn ) fn = data; data = selector; selector = undefined; } } if ( fn === false ) { fn = returnFalse; } else if ( !fn ) { return this; } if ( one === 1 ) { origFn = fn; fn = function( event ) { // Can use an empty set, since event contains the info jQuery().off( event ); return origFn.apply( this, arguments ); }; // Use same guid so caller can remove using origFn fn.guid = origFn.guid || ( origFn.guid = jQuery.guid++ ); } return this.each( function() { jQuery.event.add( this, types, fn, data, selector ); }); }, one: function( types, selector, data, fn ) { return this.on( types, selector, data, fn, 1 ); }, off: function( types, selector, fn ) { var handleObj, type; if ( types && types.preventDefault && types.handleObj ) { // ( event ) dispatched jQuery.Event handleObj = types.handleObj; jQuery( types.delegateTarget ).off( handleObj.namespace ? handleObj.origType + "." + handleObj.namespace : handleObj.origType, handleObj.selector, handleObj.handler ); return this; } if ( typeof types === "object" ) { // ( types-object [, selector] ) for ( type in types ) { this.off( type, selector, types[ type ] ); } return this; } if ( selector === false || typeof selector === "function" ) { // ( types [, fn] ) fn = selector; selector = undefined; } if ( fn === false ) { fn = returnFalse; } return this.each(function() { jQuery.event.remove( this, types, fn, selector ); }); }, trigger: function( type, data ) { return this.each(function() { jQuery.event.trigger( type, data, this ); }); }, triggerHandler: function( type, data ) { var elem = this[0]; if ( elem ) { return jQuery.event.trigger( type, data, elem, true ); } } }); var rxhtmlTag = /<(?!area|br|col|embed|hr|img|input|link|meta|param)(([\w:]+)[^>]*)\/>/gi, rtagName = /<([\w:]+)/, rhtml = /<|&#?\w+;/, rnoInnerhtml = /<(?:script|style|link)/i, // checked="checked" or checked rchecked = /checked\s*(?:[^=]|=\s*.checked.)/i, rscriptType = /^$|\/(?:java|ecma)script/i, rscriptTypeMasked = /^true\/(.*)/, rcleanScript = /^\s*\s*$/g, // We have to close these tags to support XHTML (#13200) wrapMap = { // Support: IE 9 option: [ 1, "" ], thead: [ 1, "", "
" ], col: [ 2, "", "
" ], tr: [ 2, "", "
" ], td: [ 3, "", "
" ], _default: [ 0, "", "" ] }; // Support: IE 9 wrapMap.optgroup = wrapMap.option; wrapMap.tbody = wrapMap.tfoot = wrapMap.colgroup = wrapMap.caption = wrapMap.thead; wrapMap.th = wrapMap.td; // Support: 1.x compatibility // Manipulating tables requires a tbody function manipulationTarget( elem, content ) { return jQuery.nodeName( elem, "table" ) && jQuery.nodeName( content.nodeType !== 11 ? content : content.firstChild, "tr" ) ? elem.getElementsByTagName("tbody")[0] || elem.appendChild( elem.ownerDocument.createElement("tbody") ) : elem; } // Replace/restore the type attribute of script elements for safe DOM manipulation function disableScript( elem ) { elem.type = (elem.getAttribute("type") !== null) + "/" + elem.type; return elem; } function restoreScript( elem ) { var match = rscriptTypeMasked.exec( elem.type ); if ( match ) { elem.type = match[ 1 ]; } else { elem.removeAttribute("type"); } return elem; } // Mark scripts as having already been evaluated function setGlobalEval( elems, refElements ) { var i = 0, l = elems.length; for ( ; i < l; i++ ) { data_priv.set( elems[ i ], "globalEval", !refElements || data_priv.get( refElements[ i ], "globalEval" ) ); } } function cloneCopyEvent( src, dest ) { var i, l, type, pdataOld, pdataCur, udataOld, udataCur, events; if ( dest.nodeType !== 1 ) { return; } // 1. Copy private data: events, handlers, etc. if ( data_priv.hasData( src ) ) { pdataOld = data_priv.access( src ); pdataCur = data_priv.set( dest, pdataOld ); events = pdataOld.events; if ( events ) { delete pdataCur.handle; pdataCur.events = {}; for ( type in events ) { for ( i = 0, l = events[ type ].length; i < l; i++ ) { jQuery.event.add( dest, type, events[ type ][ i ] ); } } } } // 2. Copy user data if ( data_user.hasData( src ) ) { udataOld = data_user.access( src ); udataCur = jQuery.extend( {}, udataOld ); data_user.set( dest, udataCur ); } } function getAll( context, tag ) { var ret = context.getElementsByTagName ? context.getElementsByTagName( tag || "*" ) : context.querySelectorAll ? context.querySelectorAll( tag || "*" ) : []; return tag === undefined || tag && jQuery.nodeName( context, tag ) ? jQuery.merge( [ context ], ret ) : ret; } // Support: IE >= 9 function fixInput( src, dest ) { var nodeName = dest.nodeName.toLowerCase(); // Fails to persist the checked state of a cloned checkbox or radio button. if ( nodeName === "input" && rcheckableType.test( src.type ) ) { dest.checked = src.checked; // Fails to return the selected option to the default selected state when cloning options } else if ( nodeName === "input" || nodeName === "textarea" ) { dest.defaultValue = src.defaultValue; } } jQuery.extend({ clone: function( elem, dataAndEvents, deepDataAndEvents ) { var i, l, srcElements, destElements, clone = elem.cloneNode( true ), inPage = jQuery.contains( elem.ownerDocument, elem ); // Support: IE >= 9 // Fix Cloning issues if ( !support.noCloneChecked && ( elem.nodeType === 1 || elem.nodeType === 11 ) && !jQuery.isXMLDoc( elem ) ) { // We eschew Sizzle here for performance reasons: http://jsperf.com/getall-vs-sizzle/2 destElements = getAll( clone ); srcElements = getAll( elem ); for ( i = 0, l = srcElements.length; i < l; i++ ) { fixInput( srcElements[ i ], destElements[ i ] ); } } // Copy the events from the original to the clone if ( dataAndEvents ) { if ( deepDataAndEvents ) { srcElements = srcElements || getAll( elem ); destElements = destElements || getAll( clone ); for ( i = 0, l = srcElements.length; i < l; i++ ) { cloneCopyEvent( srcElements[ i ], destElements[ i ] ); } } else { cloneCopyEvent( elem, clone ); } } // Preserve script evaluation history destElements = getAll( clone, "script" ); if ( destElements.length > 0 ) { setGlobalEval( destElements, !inPage && getAll( elem, "script" ) ); } // Return the cloned set return clone; }, buildFragment: function( elems, context, scripts, selection ) { var elem, tmp, tag, wrap, contains, j, fragment = context.createDocumentFragment(), nodes = [], i = 0, l = elems.length; for ( ; i < l; i++ ) { elem = elems[ i ]; if ( elem || elem === 0 ) { // Add nodes directly if ( jQuery.type( elem ) === "object" ) { // Support: QtWebKit // jQuery.merge because push.apply(_, arraylike) throws jQuery.merge( nodes, elem.nodeType ? [ elem ] : elem ); // Convert non-html into a text node } else if ( !rhtml.test( elem ) ) { nodes.push( context.createTextNode( elem ) ); // Convert html into DOM nodes } else { tmp = tmp || fragment.appendChild( context.createElement("div") ); // Deserialize a standard representation tag = ( rtagName.exec( elem ) || [ "", "" ] )[ 1 ].toLowerCase(); wrap = wrapMap[ tag ] || wrapMap._default; tmp.innerHTML = wrap[ 1 ] + elem.replace( rxhtmlTag, "<$1>" ) + wrap[ 2 ]; // Descend through wrappers to the right content j = wrap[ 0 ]; while ( j-- ) { tmp = tmp.lastChild; } // Support: QtWebKit // jQuery.merge because push.apply(_, arraylike) throws jQuery.merge( nodes, tmp.childNodes ); // Remember the top-level container tmp = fragment.firstChild; // Fixes #12346 // Support: Webkit, IE tmp.textContent = ""; } } } // Remove wrapper from fragment fragment.textContent = ""; i = 0; while ( (elem = nodes[ i++ ]) ) { // #4087 - If origin and destination elements are the same, and this is // that element, do not do anything if ( selection && jQuery.inArray( elem, selection ) !== -1 ) { continue; } contains = jQuery.contains( elem.ownerDocument, elem ); // Append to fragment tmp = getAll( fragment.appendChild( elem ), "script" ); // Preserve script evaluation history if ( contains ) { setGlobalEval( tmp ); } // Capture executables if ( scripts ) { j = 0; while ( (elem = tmp[ j++ ]) ) { if ( rscriptType.test( elem.type || "" ) ) { scripts.push( elem ); } } } } return fragment; }, cleanData: function( elems ) { var data, elem, type, key, special = jQuery.event.special, i = 0; for ( ; (elem = elems[ i ]) !== undefined; i++ ) { if ( jQuery.acceptData( elem ) ) { key = elem[ data_priv.expando ]; if ( key && (data = data_priv.cache[ key ]) ) { if ( data.events ) { for ( type in data.events ) { if ( special[ type ] ) { jQuery.event.remove( elem, type ); // This is a shortcut to avoid jQuery.event.remove's overhead } else { jQuery.removeEvent( elem, type, data.handle ); } } } if ( data_priv.cache[ key ] ) { // Discard any remaining `private` data delete data_priv.cache[ key ]; } } } // Discard any remaining `user` data delete data_user.cache[ elem[ data_user.expando ] ]; } } }); jQuery.fn.extend({ text: function( value ) { return access( this, function( value ) { return value === undefined ? jQuery.text( this ) : this.empty().each(function() { if ( this.nodeType === 1 || this.nodeType === 11 || this.nodeType === 9 ) { this.textContent = value; } }); }, null, value, arguments.length ); }, append: function() { return this.domManip( arguments, function( elem ) { if ( this.nodeType === 1 || this.nodeType === 11 || this.nodeType === 9 ) { var target = manipulationTarget( this, elem ); target.appendChild( elem ); } }); }, prepend: function() { return this.domManip( arguments, function( elem ) { if ( this.nodeType === 1 || this.nodeType === 11 || this.nodeType === 9 ) { var target = manipulationTarget( this, elem ); target.insertBefore( elem, target.firstChild ); } }); }, before: function() { return this.domManip( arguments, function( elem ) { if ( this.parentNode ) { this.parentNode.insertBefore( elem, this ); } }); }, after: function() { return this.domManip( arguments, function( elem ) { if ( this.parentNode ) { this.parentNode.insertBefore( elem, this.nextSibling ); } }); }, remove: function( selector, keepData /* Internal Use Only */ ) { var elem, elems = selector ? jQuery.filter( selector, this ) : this, i = 0; for ( ; (elem = elems[i]) != null; i++ ) { if ( !keepData && elem.nodeType === 1 ) { jQuery.cleanData( getAll( elem ) ); } if ( elem.parentNode ) { if ( keepData && jQuery.contains( elem.ownerDocument, elem ) ) { setGlobalEval( getAll( elem, "script" ) ); } elem.parentNode.removeChild( elem ); } } return this; }, empty: function() { var elem, i = 0; for ( ; (elem = this[i]) != null; i++ ) { if ( elem.nodeType === 1 ) { // Prevent memory leaks jQuery.cleanData( getAll( elem, false ) ); // Remove any remaining nodes elem.textContent = ""; } } return this; }, clone: function( dataAndEvents, deepDataAndEvents ) { dataAndEvents = dataAndEvents == null ? false : dataAndEvents; deepDataAndEvents = deepDataAndEvents == null ? dataAndEvents : deepDataAndEvents; return this.map(function() { return jQuery.clone( this, dataAndEvents, deepDataAndEvents ); }); }, html: function( value ) { return access( this, function( value ) { var elem = this[ 0 ] || {}, i = 0, l = this.length; if ( value === undefined && elem.nodeType === 1 ) { return elem.innerHTML; } // See if we can take a shortcut and just use innerHTML if ( typeof value === "string" && !rnoInnerhtml.test( value ) && !wrapMap[ ( rtagName.exec( value ) || [ "", "" ] )[ 1 ].toLowerCase() ] ) { value = value.replace( rxhtmlTag, "<$1>" ); try { for ( ; i < l; i++ ) { elem = this[ i ] || {}; // Remove element nodes and prevent memory leaks if ( elem.nodeType === 1 ) { jQuery.cleanData( getAll( elem, false ) ); elem.innerHTML = value; } } elem = 0; // If using innerHTML throws an exception, use the fallback method } catch( e ) {} } if ( elem ) { this.empty().append( value ); } }, null, value, arguments.length ); }, replaceWith: function() { var arg = arguments[ 0 ]; // Make the changes, replacing each context element with the new content this.domManip( arguments, function( elem ) { arg = this.parentNode; jQuery.cleanData( getAll( this ) ); if ( arg ) { arg.replaceChild( elem, this ); } }); // Force removal if there was no new content (e.g., from empty arguments) return arg && (arg.length || arg.nodeType) ? this : this.remove(); }, detach: function( selector ) { return this.remove( selector, true ); }, domManip: function( args, callback ) { // Flatten any nested arrays args = concat.apply( [], args ); var fragment, first, scripts, hasScripts, node, doc, i = 0, l = this.length, set = this, iNoClone = l - 1, value = args[ 0 ], isFunction = jQuery.isFunction( value ); // We can't cloneNode fragments that contain checked, in WebKit if ( isFunction || ( l > 1 && typeof value === "string" && !support.checkClone && rchecked.test( value ) ) ) { return this.each(function( index ) { var self = set.eq( index ); if ( isFunction ) { args[ 0 ] = value.call( this, index, self.html() ); } self.domManip( args, callback ); }); } if ( l ) { fragment = jQuery.buildFragment( args, this[ 0 ].ownerDocument, false, this ); first = fragment.firstChild; if ( fragment.childNodes.length === 1 ) { fragment = first; } if ( first ) { scripts = jQuery.map( getAll( fragment, "script" ), disableScript ); hasScripts = scripts.length; // Use the original fragment for the last item instead of the first because it can end up // being emptied incorrectly in certain situations (#8070). for ( ; i < l; i++ ) { node = fragment; if ( i !== iNoClone ) { node = jQuery.clone( node, true, true ); // Keep references to cloned scripts for later restoration if ( hasScripts ) { // Support: QtWebKit // jQuery.merge because push.apply(_, arraylike) throws jQuery.merge( scripts, getAll( node, "script" ) ); } } callback.call( this[ i ], node, i ); } if ( hasScripts ) { doc = scripts[ scripts.length - 1 ].ownerDocument; // Reenable scripts jQuery.map( scripts, restoreScript ); // Evaluate executable scripts on first document insertion for ( i = 0; i < hasScripts; i++ ) { node = scripts[ i ]; if ( rscriptType.test( node.type || "" ) && !data_priv.access( node, "globalEval" ) && jQuery.contains( doc, node ) ) { if ( node.src ) { // Optional AJAX dependency, but won't run scripts if not present if ( jQuery._evalUrl ) { jQuery._evalUrl( node.src ); } } else { jQuery.globalEval( node.textContent.replace( rcleanScript, "" ) ); } } } } } } return this; } }); jQuery.each({ appendTo: "append", prependTo: "prepend", insertBefore: "before", insertAfter: "after", replaceAll: "replaceWith" }, function( name, original ) { jQuery.fn[ name ] = function( selector ) { var elems, ret = [], insert = jQuery( selector ), last = insert.length - 1, i = 0; for ( ; i <= last; i++ ) { elems = i === last ? this : this.clone( true ); jQuery( insert[ i ] )[ original ]( elems ); // Support: QtWebKit // .get() because push.apply(_, arraylike) throws push.apply( ret, elems.get() ); } return this.pushStack( ret ); }; }); var iframe, elemdisplay = {}; /** * Retrieve the actual display of a element * @param {String} name nodeName of the element * @param {Object} doc Document object */ // Called only from within defaultDisplay function actualDisplay( name, doc ) { var style, elem = jQuery( doc.createElement( name ) ).appendTo( doc.body ), // getDefaultComputedStyle might be reliably used only on attached element display = window.getDefaultComputedStyle && ( style = window.getDefaultComputedStyle( elem[ 0 ] ) ) ? // Use of this method is a temporary fix (more like optmization) until something better comes along, // since it was removed from specification and supported only in FF style.display : jQuery.css( elem[ 0 ], "display" ); // We don't have any data stored on the element, // so use "detach" method as fast way to get rid of the element elem.detach(); return display; } /** * Try to determine the default display value of an element * @param {String} nodeName */ function defaultDisplay( nodeName ) { var doc = document, display = elemdisplay[ nodeName ]; if ( !display ) { display = actualDisplay( nodeName, doc ); // If the simple way fails, read from inside an iframe if ( display === "none" || !display ) { // Use the already-created iframe if possible iframe = (iframe || jQuery( "