[Improved display of interface files sydow@chalmers.se**20080409112508] { hunk ./ChaseImports.hs 4 +import List (isPrefixOf) hunk ./ChaseImports.hs 16 +import System hunk ./ChaseImports.hs 90 - Nothing -> do ifc <- decodeModule f + Nothing -> do (ifc,f) <- decodeModule f hunk ./ChaseImports.hs 111 -decodeModule f = catch (decodeFile f) (\e -> decodeFile (Config.libDir ++ "/" ++ f)) +decodeModule f = (do ifc <- decodeFile f + return (ifc,f)) `catch` (\e -> do ifc <- decodeFile libf + return (ifc,libf)) + where libf = Config.libDir ++ "/" ++ f hunk ./ChaseImports.hs 210 - text "\nTop level bindings\n------------------" $$ pr bs -- $$ + text "\nTop level bindings\n------------------" $$ pr (simpVars bs) -- $$ hunk ./ChaseImports.hs 214 + where simpVars (Binds rec te eqns) = Binds rec (map sV te) eqns + +sV (n,t@(Scheme rh ps ke)) = case zip (filter isGenerated (idents (Scheme rh ps []))) abcSupply of + [] -> (n,t) + s -> (n,subst s t) hunk ./ChaseImports.hs 220 +listIface cfg f = do (ifc,f) <- decodeModule f + let modul = rmSuffix ".ti" f + htmlfile = modul++".html" + if (Config.libDir `isPrefixOf` htmlfile) + then system (Config.browser cfg ++" " ++ htmlfile) + else do writeFile htmlfile (render(toHTML modul (ifc :: IFace))) + system (Config.browser cfg ++" " ++ htmlfile) hunk ./ChaseImports.hs 228 -listIface f = do ifc <- decodeModule f - putStrLn (render(pr (ifc :: IFace))) +toHTML n (IFace ns xs rs ss ds ws bs _) = text "
\n" $$ + text ("") $$ f xs $$ text "" + Types ke ds' = ds + ke' = [(n,k) | (n,k) <- ke, notElem n (dom ds')] + Binds _ te _ = bs + addSubs (n,DData vs _ cs) = (n,DData vs (map (\(_,Constr (s:_) _ _) -> s) cs1) cs2) + where (cs1,cs2) = partition (isGenerated . fst) cs + addSubs (n,DRec b vs _ ss) = (n,DRec b vs (map snd ss1) ss2) + where (ss1, ss2) = partition (isGenerated .fst) (map stripStar ss) + addSubs d = d + stripStar (n,Scheme rh ps ke) = (n,Scheme rh ps (filter (( /= Star) . snd) ke)) + te' = map (sV . stripStar) (filter (not . isGenerated . fst) te) + stripTopdecls te = bs1 ++ bs2 + where (bs1,bs2) = partition (flip elem ws . fst ) te + + hunk ./Config.hs 56 - linkFlags :: String + linkFlags :: String, + browser :: FilePath hunk ./Core.hs 421 +instance Subst Scheme Name Name where + subst s (Scheme rh ps ke) = Scheme (subst s rh) (subst s ps) (map (subKE s) ke) + where subKE s (n,k) = case lookup n s of + Just n' -> (n',k) + Nothing -> (n,k) + +instance Subst Rho Name Name where + subst s (R t) = R (subst s t) + subst s (F scs rh) = F (subst s scs) (subst s rh) + +instance Subst Type Name Name where + subst s (TId c) = case lookup c s of + Just c' -> TId c' + Nothing -> TId c + subst s (TVar _) = internalError0 "TVar in top-level type" + subst s (TAp t t') = TAp (subst s t) (subst s t') + subst s (TFun ts t) = TFun (subst s ts) (subst s t) hunk ./Core.hs 808 - prn 1 (EAp e es) = hang (prn 1 e) 2 (sep (map (prn 2) es)) + prn 1 (EAp e es) = prn 1 e <+> sep (map (prn 2) es) hunk ./Kindle.hs 316 - +instance Ids AType where + idents (TId c) = [c] + idents (TArray t) = idents t + idents TWild = [] hunk ./Main.hs 169 - let par@(Syntax.Module _ is _ _) = runM (pass parser Parser txt) + let par@(Syntax.Module n is _ _) = runM (pass parser Parser txt) hunk ./Main.hs 255 - mapM listIface i_files + mapM (listIface cfg) i_files hunk ./Main.hs 293 -checkRoot clo def = do if1 <- decodeModule (modToPath rootMod ++ ".ti") - if2 <- decodeModule (modToPath rtsMod ++ ".ti") +checkRoot clo def = do (if1,_) <- decodeModule (modToPath rootMod ++ ".ti") + (if2,_) <- decodeModule (modToPath rtsMod ++ ".ti") hunk ./Name.hs 359 -isQualified n = fromMod n /= Nothing +isQualified (Name _ _ (Just _) _) = True +isQualified _ = False + +isLocal (Name _ _ Nothing _) = True +isLocal _ = False hunk ./configure 667 +TIBROWSER hunk ./configure 2979 +# Make sure TIBROWSER is set +if test "x$TIBROWSER" = "x"; then + for ac_prog in more +do + # Extract the first word of "$ac_prog", so it can be a program name with args. +set dummy $ac_prog; ac_word=$2 +{ echo "$as_me:$LINENO: checking for $ac_word" >&5 +echo $ECHO_N "checking for $ac_word... $ECHO_C" >&6; } +if test "${ac_cv_prog_TIBROWSER+set}" = set; then + echo $ECHO_N "(cached) $ECHO_C" >&6 +else + if test -n "$TIBROWSER"; then + ac_cv_prog_TIBROWSER="$TIBROWSER" # Let the user override the test. +else +as_save_IFS=$IFS; IFS=$PATH_SEPARATOR +for as_dir in $PATH +do + IFS=$as_save_IFS + test -z "$as_dir" && as_dir=. + for ac_exec_ext in '' $ac_executable_extensions; do + if { test -f "$as_dir/$ac_word$ac_exec_ext" && $as_test_x "$as_dir/$ac_word$ac_exec_ext"; }; then + ac_cv_prog_TIBROWSER="$ac_prog" + echo "$as_me:$LINENO: found $as_dir/$ac_word$ac_exec_ext" >&5 + break 2 + fi +done +done +IFS=$as_save_IFS + +fi +fi +TIBROWSER=$ac_cv_prog_TIBROWSER +if test -n "$TIBROWSER"; then + { echo "$as_me:$LINENO: result: $TIBROWSER" >&5 +echo "${ECHO_T}$TIBROWSER" >&6; } +else + { echo "$as_me:$LINENO: result: no" >&5 +echo "${ECHO_T}no" >&6; } +fi + + + test -n "$TIBROWSER" && break +done + +fi + hunk ./configure 4885 +TIBROWSER!$TIBROWSER$ac_delim hunk ./configure 4896 - if test `sed -n "s/.*$ac_delim\$/X/p" conf$$subs.sed | grep -c X` = 57; then + if test `sed -n "s/.*$ac_delim\$/X/p" conf$$subs.sed | grep -c X` = 58; then hunk ./configure.ac 80 + +# Make sure TIBROWSER is set +if test "x$TIBROWSER" = "x"; then + AC_CHECK_PROGS(TIBROWSER,[more]) +fi hunk ./rtsPOSIX/timberc.cfg.in 5 + , browser = "@TIBROWSER@ " }