module SWlib where import System.Posix import IO import Random import Array import List import qualified Xhtml1 as X [] $$ _ = "" ((n,v):ps) $$ n' | n == n' = v | otherwise = ps $$ n' encodeDQ = map (\c->if c=='\"' then '$' else c) decodeDQ = map (\c->if c=='$' then '\"' else c) filecontent name = do h <- openFile name ReadMode s <- hGetContents h return s random_shuffle [] g = ([], g) random_shuffle l g = (\(a,g)->(elems a, g)) $ random_shuffle_array a g where a = listArray (0,length l-1) l random_shuffle_array a g = rs a g hi where (lo, hi) = bounds a rs a g n | lo < n = rs (swap k n) g' n' | otherwise = (a, g) where n' = pred n (k, g') = randomR (lo, n') g swap i j = a//[(i,a!j),(j,a!i)] validxhtml1 = X.a X.!["href"X.-="http://validator.w3.org/check/referer"] X.<< X.img "http://www.w3.org/Icons/valid-xhtml10" "Valid XHTML 1.0!" withEucKrEnv = (setEnv "LANG" "ko_KR.EUC-KR" True >>)