diff options
author | David Terei <davidterei@gmail.com> | 2011-07-20 11:09:03 -0700 |
---|---|---|
committer | David Terei <davidterei@gmail.com> | 2011-07-20 11:26:35 -0700 |
commit | 16514f272fb42af6e9c7674a9bd6c9dce369231f (patch) | |
tree | e4f332b45fe65e2a7a2451be5674f887b42bf199 /testsuite/tests/codeGen/should_compile | |
parent | ebd422aed41048476aa61dd4c520d43becd78682 (diff) | |
download | haskell-16514f272fb42af6e9c7674a9bd6c9dce369231f.tar.gz |
Move tests from tests/ghc-regress/* to just tests/*
Diffstat (limited to 'testsuite/tests/codeGen/should_compile')
19 files changed, 913 insertions, 0 deletions
diff --git a/testsuite/tests/codeGen/should_compile/1916.hs b/testsuite/tests/codeGen/should_compile/1916.hs new file mode 100644 index 0000000000..7210aaf41c --- /dev/null +++ b/testsuite/tests/codeGen/should_compile/1916.hs @@ -0,0 +1,3 @@ +module Bug (tst) where +tst :: Float -> Bool +tst x = truncate x > (0::Int) diff --git a/testsuite/tests/codeGen/should_compile/2388.hs b/testsuite/tests/codeGen/should_compile/2388.hs new file mode 100644 index 0000000000..f3364f5b6e --- /dev/null +++ b/testsuite/tests/codeGen/should_compile/2388.hs @@ -0,0 +1,14 @@ +module Q where + +import Data.Bits +import Data.Word +import Data.Int + +test1 :: Word32 -> Char +test1 w | w .&. 0x80000000 /= 0 = 'a' +test1 _ = 'b' + +-- this should use a testq instruction on x86_64 +test2 :: Int64 -> Char +test2 w | w .&. (-3) /= 0 = 'a' +test2 _ = 'b' diff --git a/testsuite/tests/codeGen/should_compile/2578.hs b/testsuite/tests/codeGen/should_compile/2578.hs new file mode 100644 index 0000000000..c851b54f88 --- /dev/null +++ b/testsuite/tests/codeGen/should_compile/2578.hs @@ -0,0 +1,17 @@ + +{-# LANGUAGE EmptyDataDecls #-} + +-- This used to give warnings: +-- ld: atom sorting error for _Main_MyType_closure_tbl and _Main_MyType2_closure_tbl in q.o +-- ld: atom sorting error for _Main_MyType_closure_tbl and _Main_MyType2_closure_tbl in q.o +-- ld: atom sorting error for _Main_MyType_closure_tbl and _Main_MyType2_closure_tbl in q.o +-- when compiling on OS X (trac #2578). + +module Main (main) where + +data MyType +data MyType2 + +main :: IO () +main = print () + diff --git a/testsuite/tests/codeGen/should_compile/3132.hs b/testsuite/tests/codeGen/should_compile/3132.hs new file mode 100644 index 0000000000..c6aa2579e9 --- /dev/null +++ b/testsuite/tests/codeGen/should_compile/3132.hs @@ -0,0 +1,6 @@ +module Spring where + +import Data.Array.Unboxed + +step :: UArray Int Double -> [Double] +step y = [y!1 + y!0] diff --git a/testsuite/tests/codeGen/should_compile/3579.hs b/testsuite/tests/codeGen/should_compile/3579.hs new file mode 100644 index 0000000000..29711e147b --- /dev/null +++ b/testsuite/tests/codeGen/should_compile/3579.hs @@ -0,0 +1,7 @@ +module Bug where + +compose :: [a -> a] -> a -> a +compose = foldr (.) id + +class Compose a where + compose1 :: a -> a -> a diff --git a/testsuite/tests/codeGen/should_compile/Makefile b/testsuite/tests/codeGen/should_compile/Makefile new file mode 100644 index 0000000000..ff43099198 --- /dev/null +++ b/testsuite/tests/codeGen/should_compile/Makefile @@ -0,0 +1,7 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +2578: + '$(TEST_HC)' $(TEST_HC_OPTS) --make 2578 -fforce-recomp -v0 + diff --git a/testsuite/tests/codeGen/should_compile/T3286.hs b/testsuite/tests/codeGen/should_compile/T3286.hs new file mode 100644 index 0000000000..0cc852db94 --- /dev/null +++ b/testsuite/tests/codeGen/should_compile/T3286.hs @@ -0,0 +1,45 @@ + +module T3286 (train) where + +import qualified Data.Map as M +import Data.List (groupBy, foldl') +import Data.Maybe (fromMaybe, fromJust) +import Data.Function (on) +import T3286b + +type Prob = LogFloat + +learn_states :: (Ord state) => [(observation, state)] -> M.Map state Prob +learn_states xs = histogram $ map snd xs + +learn_observations :: (Ord state, Ord observation) => + M.Map state Prob + -> [(observation, state)] + -> M.Map (observation, state) Prob +learn_observations state_prob = M.mapWithKey f . histogram + where f (_, state) prob = prob / (fromJust $ M.lookup state state_prob) + +histogram :: (Ord a) => [a] -> M.Map a Prob +histogram xs = let hist = foldl' undefined M.empty xs in + M.map (/ M.foldrWithKey (\_ a b -> a + b) 0 hist) hist + +train :: (Ord observation, Ord state) => + [(observation, state)] + -> (observation -> [Prob]) +train sample = model + where + states = learn_states sample + state_list = M.keys states + + observations = learn_observations states sample + observation_probs = fromMaybe (fill state_list []) . (flip M.lookup $ + M.fromList $ map (\ (e, xs) -> (e, fill state_list xs)) $ + map (\ xs -> (fst $ head xs, map snd xs)) $ + groupBy ((==) `on` fst) + [(observation, (state, prob)) + | ((observation, state), prob) <- M.toAscList observations]) + + model = observation_probs + + fill :: Eq state => [state] -> [(state, Prob)] -> [Prob] + fill = undefined diff --git a/testsuite/tests/codeGen/should_compile/T3286b.hs b/testsuite/tests/codeGen/should_compile/T3286b.hs new file mode 100644 index 0000000000..f6c1fdbeac --- /dev/null +++ b/testsuite/tests/codeGen/should_compile/T3286b.hs @@ -0,0 +1,15 @@ + +{-# LANGUAGE GeneralizedNewtypeDeriving #-} + +module T3286b (LogFloat) where + +newtype LogFloat = LogFloat Double + deriving (Eq, Ord, Num, Show) + +instance Fractional LogFloat where + (/) (LogFloat x) (LogFloat y) + | x == 1 + && y == 1 = error "(/)" + | otherwise = LogFloat (x-y) + fromRational = LogFloat . fromRational + diff --git a/testsuite/tests/codeGen/should_compile/all.T b/testsuite/tests/codeGen/should_compile/all.T new file mode 100644 index 0000000000..ba29c2a145 --- /dev/null +++ b/testsuite/tests/codeGen/should_compile/all.T @@ -0,0 +1,19 @@ +test('cg001', only_compiler_types(['ghc']), compile, ['']) +test('cg002', normal, compile, ['']) +test('cg003', only_ways(['optasm']), compile, ['']) +test('cg004', normal, compile, ['']) +test('cg005', only_ways(['optasm']), compile, ['']) +test('cg006', normal, compile, ['']) +test('cg007', normal, compile, ['']) +test('cg008', normal, compile, ['']) + +test('1916', normal, compile, ['']) +test('2388', normal, compile, ['']) +test('3132', normal, compile, ['-dcmm-lint']) +test('T3286', extra_clean(['T3286b.o','T3286b.hi']), + multimod_compile, ['T3286', '-v0']) +test('3579', normal, compile, ['']) +test('2578', normal, run_command, ['$MAKE -s --no-print-directory 2578']) +# skip llvm on i386 as we don't support fPIC +test('jmp_tbl', if_arch('i386', omit_ways(['llvm', 'optllvm'])), compile, ['-fPIC -O']) +test('massive_array', if_arch('i386', omit_ways(['llvm', 'optllvm'])), compile, ['-fPIC']) diff --git a/testsuite/tests/codeGen/should_compile/cg001.hs b/testsuite/tests/codeGen/should_compile/cg001.hs new file mode 100644 index 0000000000..ad00a8f89c --- /dev/null +++ b/testsuite/tests/codeGen/should_compile/cg001.hs @@ -0,0 +1,15 @@ +{-# LANGUAGE MagicHash #-} + +module ShouldCompile where + +import GHC.Exts + +data STRef s a = STRef (MutVar# s a) + +-- ghc 4.08 had a problem with returning a MutVar#. + +from :: STRef s a -> MutVar# s a +from (STRef x) = x + +to :: MutVar# s a -> STRef s a +to x = STRef x diff --git a/testsuite/tests/codeGen/should_compile/cg002.hs b/testsuite/tests/codeGen/should_compile/cg002.hs new file mode 100644 index 0000000000..9d655d9d12 --- /dev/null +++ b/testsuite/tests/codeGen/should_compile/cg002.hs @@ -0,0 +1,5 @@ + +module M where +import Data.Char +{-# INLINE f #-} +f = map ord . map chr diff --git a/testsuite/tests/codeGen/should_compile/cg003.hs b/testsuite/tests/codeGen/should_compile/cg003.hs new file mode 100644 index 0000000000..e7cea2e0b3 --- /dev/null +++ b/testsuite/tests/codeGen/should_compile/cg003.hs @@ -0,0 +1,7 @@ +module Test where + +-- !!! caused compiler to generate bogus HC code, fixed in +-- basicTypes/Literal.lhs rev. 1.36. + +f :: Double -> Int +f x = round (x - (-5.0)) diff --git a/testsuite/tests/codeGen/should_compile/cg004.hs b/testsuite/tests/codeGen/should_compile/cg004.hs new file mode 100644 index 0000000000..fb8e3cc413 --- /dev/null +++ b/testsuite/tests/codeGen/should_compile/cg004.hs @@ -0,0 +1,30 @@ +module ShouldCompile where + +-- Killed GHC 6.0 in isCrossDllArg +-- +-- ghc-6.0: panic! (the `impossible' happened, GHC version 6.0): +-- coreSyn/CoreUtils.lhs:1188: Non-exhaustive patterns in function isCrossDllArg +-- +-- The reason was that newST had the form +-- newST = \ @ v -> GHC.Base.: +-- @ (Environment.Scope v) +-- (case $fScopeOpersScope @ v +-- of tpl_B1 { Environment.:DScopeOpers tpl_B2 tpl_B3 -> +-- tpl_B2 +-- }) +-- (GHC.Base.[] @ (Environment.Scope v)) + +class ScopeOpers s where + emptyScope :: s + op :: s -> s + +data Scope v = NewScope + +instance ScopeOpers (Scope v) where + emptyScope = error "emptyScope" + op = error "op" + +newtype SymbolTable v = SymbolTable [Scope v] + +newST :: SymbolTable v +newST = SymbolTable [emptyScope] diff --git a/testsuite/tests/codeGen/should_compile/cg005.hs b/testsuite/tests/codeGen/should_compile/cg005.hs new file mode 100644 index 0000000000..a25ad4250a --- /dev/null +++ b/testsuite/tests/codeGen/should_compile/cg005.hs @@ -0,0 +1,20 @@ +module Bug where
+
+import Foreign hiding ( unsafePerformIO )
+import Foreign.ForeignPtr
+import Data.Char
+import System.IO.Unsafe
+
+data PackedString = PS !(ForeignPtr Word8) !Int !Int
+
+(!) :: PackedString -> Int -> Word8
+(PS x s _l) ! i
+ = unsafePerformIO $ withForeignPtr x $ \p -> peekElemOff p (s+i)
+
+w2c :: Word8 -> Char
+w2c = chr . fromIntegral
+
+indexPS :: PackedString -> Int -> Char
+indexPS theps i | i < 0 = error "Negative index in indexPS"
+ | otherwise = w2c $ theps ! i
+
diff --git a/testsuite/tests/codeGen/should_compile/cg006.hs b/testsuite/tests/codeGen/should_compile/cg006.hs new file mode 100644 index 0000000000..494b37937b --- /dev/null +++ b/testsuite/tests/codeGen/should_compile/cg006.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE MagicHash #-} +module ShouldCompile where + +-- exposed a bug in the NCG in 6.4.2 +import GHC.Base +class Unboxable a where + writeUnboxable :: MutableByteArray# RealWorld -> a -> State# RealWorld -> State# RealWorld + writeUnboxable arr a s = writeInt8Array# arr 0# (getTag 0) s diff --git a/testsuite/tests/codeGen/should_compile/cg007.hs b/testsuite/tests/codeGen/should_compile/cg007.hs new file mode 100644 index 0000000000..5ef739bd47 --- /dev/null +++ b/testsuite/tests/codeGen/should_compile/cg007.hs @@ -0,0 +1,26 @@ +{-# LANGUAGE ForeignFunctionInterface #-} +module ShouldCompile where + +import Foreign.C.Types + +{- +During 6.11, this was failing like this: + +In file included from /ghc/includes/Stg.h:207, + + from /tmp/ghc2904_0/ghc2904_0.hc:3:0: +/tmp/ghc2904_0/ghc2904_0.hc: In function `swM_ret': + +/tmp/ghc2904_0/ghc2904_0.hc:22:0: + error: `gamma' undeclared (first use in this function) + +/tmp/ghc2904_0/ghc2904_0.hc:22:0: + error: (Each undeclared identifier is reported only once + +/tmp/ghc2904_0/ghc2904_0.hc:22:0: + error: for each function it appears in.) +-} + +foreign import ccall unsafe "math.h gamma" + gamma :: CDouble -> CDouble + diff --git a/testsuite/tests/codeGen/should_compile/cg008.hs b/testsuite/tests/codeGen/should_compile/cg008.hs new file mode 100644 index 0000000000..10099c1b48 --- /dev/null +++ b/testsuite/tests/codeGen/should_compile/cg008.hs @@ -0,0 +1,21 @@ +{-# LANGUAGE MagicHash, BangPatterns #-} +{-# OPTIONS_GHC -O0 #-} + +-- Variant of cgrun066; compilation as a module is different. + +module Cg008 (hashStr) where + +import Foreign.C +import Data.Word +import Foreign.Ptr +import GHC.Exts + +import Control.Exception + +hashStr :: Ptr Word8 -> Int -> Int +hashStr (Ptr a#) (I# len#) = loop 0# 0# + where + loop h n | n GHC.Exts.==# len# = I# h + | otherwise = loop h2 (n GHC.Exts.+# 1#) + where !c = ord# (indexCharOffAddr# a# n) + !h2 = (c GHC.Exts.+# (h GHC.Exts.*# 128#)) `remInt#` 4091# diff --git a/testsuite/tests/codeGen/should_compile/jmp_tbl.hs b/testsuite/tests/codeGen/should_compile/jmp_tbl.hs new file mode 100644 index 0000000000..56904ed7a1 --- /dev/null +++ b/testsuite/tests/codeGen/should_compile/jmp_tbl.hs @@ -0,0 +1,128 @@ +{-# LANGUAGE NamedFieldPuns #-} + +{- +This funny module was reduced from a failing build of stage2 using +the new code generator and the linear register allocator, with this bug: + +"inplace/bin/ghc-stage1" -fPIC -dynamic -H32m -O -Wall -H64m -O0 -package-name ghc-7.1.20110414 -hide-all-packages -i -icompiler/basicTypes -icompiler/cmm -icompiler/codeGen -icompiler/coreSyn -icompiler/deSugar -icompiler/ghci -icompiler/hsSyn -icompiler/iface -icompiler/llvmGen -icompiler/main -icompiler/nativeGen -icompiler/parser -icompiler/prelude -icompiler/profiling -icompiler/rename -icompiler/simplCore -icompiler/simplStg -icompiler/specialise -icompiler/stgSyn -icompiler/stranal -icompiler/typecheck -icompiler/types -icompiler/utils -icompiler/vectorise -icompiler/stage2/build -icompiler/stage2/build/autogen -Icompiler/stage2/build -Icompiler/stage2/build/autogen -Icompiler/../libffi/build/include -Icompiler/stage2 -Icompiler/../libraries/base/cbits -Icompiler/../libraries/base/include -Icompiler/. -Icompiler/parser -Icompiler/utils -optP-DGHCI -optP-include -optPcompiler/stage2/build/autogen/cabal_macros.h -package Cabal-1.11.0 -package array-0.3.0.2 -package base-4.3.1.0 -package bin-package-db-0.0.0.0 -package bytestring-0.9.1.10 -package containers-0.4.0.0 -package directory-1.1.0.0 -package filepath-1.2.0.0 -package hoopl-3.8.7.0 -package hpc-0.5.0.6 -package old-time-1.0.0.6 -package process-1.0.1.4 -package template-haskell-2.5.0.0 -package unix-2.4.1.0 -Wall -fno-warn-name-shadowing -fno-warn-orphans -XHaskell98 -XNondecreasingIndentation -XCPP -XMagicHash -XUnboxedTuples -XPatternGuards -XForeignFunctionInterface -XEmptyDataDecls -XTypeSynonymInstances -XMultiParamTypeClasses -XFlexibleInstances -XRank2Types -XScopedTypeVariables -XDeriveDataTypeable -DGHCI_TABLES_NEXT_TO_CODE -DSTAGE=2 -O2 -O -DGHC_DEFAULT_NEW_CODEGEN -no-user-package-conf -rtsopts -odir compiler/stage2/build -hidir compiler/stage2/build -stubdir compiler/stage2/build -hisuf dyn_hi -osuf dyn_o -hcsuf dyn_hc -c compiler/main/DriverPipeline.hs -o compiler/stage2/build/DriverPipeline.dyn_o -fforce-recomp -dno-debug-output -fno-warn-unused-binds + +ghc-stage1: panic! (the 'impossible' happened) + (GHC version 7.1.20110414 for x86_64-unknown-linux): + Cannot patch JMP_TBL + +This panic only appears to show up on x86-64 and with -fPIC. I wasn't +able to get the produced optimized C-- to crash the linear register +allocator. To see the bug, you need some extra patches for the new code +generator, in particular, this set (which can be acquired from the +jmp_tbl_bug tag at <https://github.com/ezyang/ghc>): + + commit 7b275c93df7944f0a9b51034cf1f64e3e70582a5 + Author: Edward Z. Yang <ezyang@mit.edu> + Date: Thu Apr 14 21:20:21 2011 +0100 + + Give manifestSP better information about the actual SP location. + + This patch fixes silliness where the SP pointer is continually + bumped up and down. + + Signed-off-by: Edward Z. Yang <ezyang@mit.edu> + + commit 5b5add4246d3997670ae995f7d2a028db92fff95 + Author: Edward Z. Yang <ezyang@mit.edu> + Date: Wed Apr 13 11:16:36 2011 +0100 + + Generalized assignment rewriting pass. + + This assignment rewriting pass subsumes the previous reload + sinking pass, and also performs basic inlining. + + Signed-off-by: Edward Z. Yang <ezyang@mit.edu> + +The ostensible cause is that the linear register allocator is getting +really unlucky and needs to insert a fixup block after precisely one +jump in a jump table, because the block it jumps to was processed +already. As you can see, actually getting the linear register allocator +into this funk is /very/ difficult. + +-} + +module DriverPipeline (compileFile) where + +import Control.Exception + +data Phase + = Unlit () + | Ccpp + | Cc + | Cobjc + | HCc + | SplitAs + | As + | LlvmOpt + | LlvmLlc + | LlvmMangle + | MergeStub + | StopLn + deriving (Show) + +data PipeState = PipeState { + stop_phase :: Phase, + src_basename :: String, + output_spec :: (), + hsc_env :: Maybe String, + maybe_loc :: Maybe String + } + +newtype CompPipeline a = P { unP :: PipeState -> IO (PipeState, a) } + +instance Monad CompPipeline where + return a = P $ \state -> return (state, a) + P m >>= k = P $ \state -> do (state',a) <- m state + unP (k a) state' + +eqPhase :: Phase -> Phase -> Bool +eqPhase (Unlit _) (Unlit _) = True +eqPhase Ccpp Ccpp = True +eqPhase Cc Cc = True +eqPhase HCc HCc = True +eqPhase SplitAs SplitAs = True +eqPhase As As = True +eqPhase LlvmOpt LlvmOpt = True +eqPhase LlvmLlc LlvmLlc = True +eqPhase LlvmMangle LlvmMangle = True +eqPhase MergeStub MergeStub = True +eqPhase StopLn StopLn = True +eqPhase _ _ = False + +compileFile start_phase state = do + unP (pipeLoop start_phase) state + getOutputFilename undefined undefined undefined undefined undefined undefined + +pipeLoop phase = do + dflags@PipeState{stop_phase} <- getPipeState + io $ evaluate (phase `eqPhase` stop_phase) + runPhase phase dflags + pipeLoop phase + +getOutputFilename :: Phase -> () -> String -> Maybe String -> Phase -> Maybe String -> IO String +getOutputFilename p o b md p' ml + | p' `eqPhase` p, () <- o = undefined + | Just l <- ml = return l + | Just d <- md = return $ d ++ b + | otherwise = undefined + +runPhase p _ | p `eqPhase` Cc || p `eqPhase` Ccpp || p `eqPhase` HCc || p `eqPhase` Cobjc = undefined +runPhase LlvmMangle _ = undefined +runPhase SplitAs _ = undefined +runPhase LlvmOpt _ = undefined +runPhase LlvmLlc dflags = phaseOutputFilename >> io (evaluate dflags) >> return undefined +runPhase MergeStub _ = phaseOutputFilename >> undefined +runPhase other _ = io (evaluate (show other)) >> undefined + +phaseOutputFilename :: CompPipeline () +phaseOutputFilename = do + PipeState{stop_phase, src_basename, output_spec, maybe_loc, hsc_env} <- getPipeState + io $ getOutputFilename stop_phase output_spec src_basename hsc_env StopLn maybe_loc + +getPipeState = P $ \state -> return (state, state) +io m = P $ \state -> do a <- m; return (state, ()) diff --git a/testsuite/tests/codeGen/should_compile/massive_array.hs b/testsuite/tests/codeGen/should_compile/massive_array.hs new file mode 100644 index 0000000000..a9db12bc4c --- /dev/null +++ b/testsuite/tests/codeGen/should_compile/massive_array.hs @@ -0,0 +1,520 @@ +{-# OPTIONS_GHC -fno-ignore-interface-pragmas -fasm #-} + +-- This test breaks the linear register allocator when compiled the +-- flags -fnew-codegen, -fPIC and -dynamic, running out of stack +-- slots. You actually don't need 500 elements; 32-bit fails +-- with only about 260 or so. Works for stage1 too! It's a bit touchy +-- about optimization flags; if you specify -O or -O0 in OPTIONS_GHC +-- the bug goes away. Shows up in GHC 7.0.3. +-- +-- The -fno-ignore-interface-pragmas flag is pretty important! (Though I +-- don't quite know why yet.) Gigantic arrays like this show up in +-- generated code, in particular Parser.hs from Happy in GHC. + +module MassiveArray where + +import Data.Array + +f = array (0, 499) + $ [ + (0, 0), + (1, 1), + (2, 2), + (3, 3), + (4, 4), + (5, 5), + (6, 6), + (7, 7), + (8, 8), + (9, 9), + (10, 10), + (11, 11), + (12, 12), + (13, 13), + (14, 14), + (15, 15), + (16, 16), + (17, 17), + (18, 18), + (19, 19), + (20, 20), + (21, 21), + (22, 22), + (23, 23), + (24, 24), + (25, 25), + (26, 26), + (27, 27), + (28, 28), + (29, 29), + (30, 30), + (31, 31), + (32, 32), + (33, 33), + (34, 34), + (35, 35), + (36, 36), + (37, 37), + (38, 38), + (39, 39), + (40, 40), + (41, 41), + (42, 42), + (43, 43), + (44, 44), + (45, 45), + (46, 46), + (47, 47), + (48, 48), + (49, 49), + (50, 50), + (51, 51), + (52, 52), + (53, 53), + (54, 54), + (55, 55), + (56, 56), + (57, 57), + (58, 58), + (59, 59), + (60, 60), + (61, 61), + (62, 62), + (63, 63), + (64, 64), + (65, 65), + (66, 66), + (67, 67), + (68, 68), + (69, 69), + (70, 70), + (71, 71), + (72, 72), + (73, 73), + (74, 74), + (75, 75), + (76, 76), + (77, 77), + (78, 78), + (79, 79), + (80, 80), + (81, 81), + (82, 82), + (83, 83), + (84, 84), + (85, 85), + (86, 86), + (87, 87), + (88, 88), + (89, 89), + (90, 90), + (91, 91), + (92, 92), + (93, 93), + (94, 94), + (95, 95), + (96, 96), + (97, 97), + (98, 98), + (99, 99), + (100, 100), + (101, 101), + (102, 102), + (103, 103), + (104, 104), + (105, 105), + (106, 106), + (107, 107), + (108, 108), + (109, 109), + (110, 110), + (111, 111), + (112, 112), + (113, 113), + (114, 114), + (115, 115), + (116, 116), + (117, 117), + (118, 118), + (119, 119), + (120, 120), + (121, 121), + (122, 122), + (123, 123), + (124, 124), + (125, 125), + (126, 126), + (127, 127), + (128, 128), + (129, 129), + (130, 130), + (131, 131), + (132, 132), + (133, 133), + (134, 134), + (135, 135), + (136, 136), + (137, 137), + (138, 138), + (139, 139), + (140, 140), + (141, 141), + (142, 142), + (143, 143), + (144, 144), + (145, 145), + (146, 146), + (147, 147), + (148, 148), + (149, 149), + (150, 150), + (151, 151), + (152, 152), + (153, 153), + (154, 154), + (155, 155), + (156, 156), + (157, 157), + (158, 158), + (159, 159), + (160, 160), + (161, 161), + (162, 162), + (163, 163), + (164, 164), + (165, 165), + (166, 166), + (167, 167), + (168, 168), + (169, 169), + (170, 170), + (171, 171), + (172, 172), + (173, 173), + (174, 174), + (175, 175), + (176, 176), + (177, 177), + (178, 178), + (179, 179), + (180, 180), + (181, 181), + (182, 182), + (183, 183), + (184, 184), + (185, 185), + (186, 186), + (187, 187), + (188, 188), + (189, 189), + (190, 190), + (191, 191), + (192, 192), + (193, 193), + (194, 194), + (195, 195), + (196, 196), + (197, 197), + (198, 198), + (199, 199), + (200, 200), + (201, 201), + (202, 202), + (203, 203), + (204, 204), + (205, 205), + (206, 206), + (207, 207), + (208, 208), + (209, 209), + (210, 210), + (211, 211), + (212, 212), + (213, 213), + (214, 214), + (215, 215), + (216, 216), + (217, 217), + (218, 218), + (219, 219), + (220, 220), + (221, 221), + (222, 222), + (223, 223), + (224, 224), + (225, 225), + (226, 226), + (227, 227), + (228, 228), + (229, 229), + (230, 230), + (231, 231), + (232, 232), + (233, 233), + (234, 234), + (235, 235), + (236, 236), + (237, 237), + (238, 238), + (239, 239), + (240, 240), + (241, 241), + (242, 242), + (243, 243), + (244, 244), + (245, 245), + (246, 246), + (247, 247), + (248, 248), + (249, 249), + (250, 250), + (251, 251), + (252, 252), + (253, 253), + (254, 254), + (255, 255), + (256, 256), + (257, 257), + (258, 258), + (259, 259), + (260, 260), + (261, 261), + (262, 262), + (263, 263), + (264, 264), + (265, 265), + (266, 266), + (267, 267), + (268, 268), + (269, 269), + (270, 270), + (271, 271), + (272, 272), + (273, 273), + (274, 274), + (275, 275), + (276, 276), + (277, 277), + (278, 278), + (279, 279), + (280, 280), + (281, 281), + (282, 282), + (283, 283), + (284, 284), + (285, 285), + (286, 286), + (287, 287), + (288, 288), + (289, 289), + (290, 290), + (291, 291), + (292, 292), + (293, 293), + (294, 294), + (295, 295), + (296, 296), + (297, 297), + (298, 298), + (299, 299), + (300, 300), + (301, 301), + (302, 302), + (303, 303), + (304, 304), + (305, 305), + (306, 306), + (307, 307), + (308, 308), + (309, 309), + (310, 310), + (311, 311), + (312, 312), + (313, 313), + (314, 314), + (315, 315), + (316, 316), + (317, 317), + (318, 318), + (319, 319), + (320, 320), + (321, 321), + (322, 322), + (323, 323), + (324, 324), + (325, 325), + (326, 326), + (327, 327), + (328, 328), + (329, 329), + (330, 330), + (331, 331), + (332, 332), + (333, 333), + (334, 334), + (335, 335), + (336, 336), + (337, 337), + (338, 338), + (339, 339), + (340, 340), + (341, 341), + (342, 342), + (343, 343), + (344, 344), + (345, 345), + (346, 346), + (347, 347), + (348, 348), + (349, 349), + (350, 350), + (351, 351), + (352, 352), + (353, 353), + (354, 354), + (355, 355), + (356, 356), + (357, 357), + (358, 358), + (359, 359), + (360, 360), + (361, 361), + (362, 362), + (363, 363), + (364, 364), + (365, 365), + (366, 366), + (367, 367), + (368, 368), + (369, 369), + (370, 370), + (371, 371), + (372, 372), + (373, 373), + (374, 374), + (375, 375), + (376, 376), + (377, 377), + (378, 378), + (379, 379), + (380, 380), + (381, 381), + (382, 382), + (383, 383), + (384, 384), + (385, 385), + (386, 386), + (387, 387), + (388, 388), + (389, 389), + (390, 390), + (391, 391), + (392, 392), + (393, 393), + (394, 394), + (395, 395), + (396, 396), + (397, 397), + (398, 398), + (399, 399), + (400, 400), + (401, 401), + (402, 402), + (403, 403), + (404, 404), + (405, 405), + (406, 406), + (407, 407), + (408, 408), + (409, 409), + (410, 410), + (411, 411), + (412, 412), + (413, 413), + (414, 414), + (415, 415), + (416, 416), + (417, 417), + (418, 418), + (419, 419), + (420, 420), + (421, 421), + (422, 422), + (423, 423), + (424, 424), + (425, 425), + (426, 426), + (427, 427), + (428, 428), + (429, 429), + (430, 430), + (431, 431), + (432, 432), + (433, 433), + (434, 434), + (435, 435), + (436, 436), + (437, 437), + (438, 438), + (439, 439), + (440, 440), + (441, 441), + (442, 442), + (443, 443), + (444, 444), + (445, 445), + (446, 446), + (447, 447), + (448, 448), + (449, 449), + (450, 450), + (451, 451), + (452, 452), + (453, 453), + (454, 454), + (455, 455), + (456, 456), + (457, 457), + (458, 458), + (459, 459), + (460, 460), + (461, 461), + (462, 462), + (463, 463), + (464, 464), + (465, 465), + (466, 466), + (467, 467), + (468, 468), + (469, 469), + (470, 470), + (471, 471), + (472, 472), + (473, 473), + (474, 474), + (475, 475), + (476, 476), + (477, 477), + (478, 478), + (479, 479), + (480, 480), + (481, 481), + (482, 482), + (483, 483), + (484, 484), + (485, 485), + (486, 486), + (487, 487), + (488, 488), + (489, 489), + (490, 490), + (491, 491), + (492, 492), + (493, 493), + (494, 494), + (495, 495), + (496, 496), + (497, 497), + (498, 498), + (499, 499) + ] |