Hello,

I spent some time to make Yi work with 6.8, and failed up to now.
Before I go into details, let's see what I'm trying to do with Yi.

The idea is to have a fully dynamic application where the user is
allowed to run arbitrary haskell code on the command line. This can be
used to quickly test new code, etc. In particular, one needs to be
able to "reload" the configuration in that manner.

This is achieved basically by having everything running inside a
specially made "GHC Session". The dynamic code is able to "reload
itself" because it is passed a pointer to the GHC session.

The GHC experts will see here that this cannot work :) Indeed, GHC has
a number of "global variables", which, if accessed through code loaded
in a GHC session, will be instanciated again. This means that
accessing a "level 1" session with "level 2" code is normally not
possible.

However, I found a workaround: encapsulate all calls to the GHC API in
a data structure in "level 1" code, which is then passed to "level 2".
(A haskell version of C-style callbacks). While this worked
beautifully with GHC 6.6, it fails with 6.8rc. with

  exception :: GhcException
  yi: panic! (the 'impossible' happened)
    (GHC version 6.8.0.20071019 for i386-unknown-linux):
          a static opt was looked at too early!

This happens at a seemingly unrelated point in the code. (inside the
bytecode interpreter?)

I can't really report a bug here, because what I'm trying to do is
probably fairly unsupported by GHC. However, I'd appreciate some sort
of advice. Is my workaround the correct approach? How would GHC people
implement a dynamic application? Should I drop the idea completely?
...

Thanks in advance for your help :)
-- JP

Attached: a darcs patch to the Yi repo to (try to) support 6.8.
New patches:

[adapt to GHC 6.8
[EMAIL PROTECTED] {
hunk ./Makefile 13
-	dist/build/yi/yi -B. -f$(frontend)
+	cp --preserve=timestamps -R Yi dist/build
+	dist/build/yi/yi -Bdist/build -f$(frontend)
hunk ./Setup.hs 4
-import Control.Monad(when, filterM, unless)
-import Data.List (intersect)
+import Control.Monad
hunk ./Setup.hs 7
-import Distribution.Setup
+import Distribution.Simple.Setup
hunk ./Setup.hs 9
+import Distribution.Simple.GHC as GHC
hunk ./Setup.hs 11
-import Distribution.Simple.Utils
+import Distribution.Simple.Program
+import Distribution.Verbosity
hunk ./Setup.hs 14
-import System.Exit
hunk ./Setup.hs 15
-import System.Info
-import System.Process
hunk ./Setup.hs 16
+import Control.Applicative
hunk ./Setup.hs 22
-getLibDir ghcPath = do 
-          (_, out, _, pid) <- runInteractiveProcess ghcPath ["--print-libdir"]
-                                                           Nothing Nothing
-          libDir <- hGetLine out
-          waitForProcess pid
-          return libDir
-
hunk ./Setup.hs 24
-bHook :: PackageDescription -> LocalBuildInfo -> Maybe UserHooks -> BuildFlags -> IO ()
-bHook pd lbi hooks bfs = do
-  let ghc = compilerPath . compiler $ lbi
+-- TODO: add a configuration hook that does not want to build for
+-- certain combination of flags
+
+bHook :: PackageDescription -> LocalBuildInfo -> UserHooks -> BuildFlags -> IO ()
+bHook pd lbi hooks flags = do
+  let verbosity = buildVerbose flags
hunk ./Setup.hs 31
+      ghcOut = rawSystemProgramStdoutConf verbosity ghcProgram (withPrograms lbi)
hunk ./Setup.hs 33
-  libdir <- getLibDir ghc
+  libdir <- head . lines <$> ghcOut ["--print-libdir"]
+  putStrLn $ "GHC libdir = " ++ show libdir
hunk ./Setup.hs 39
-  buildHook defaultUserHooks pd' lbi hooks bfs
+  buildHook defaultUserHooks pd' lbi hooks flags
hunk ./Setup.hs 41
-  res <- mapM (precompile ghc) precompiles
-  let sucessfuls = [m | (m,code) <- res, code == ExitSuccess]
-      nok = null $ intersect sucessfuls ["Yi.Vty.UI", "Yi.Gtk.UI"]
-  putStrLn $ "Sucessfully compiled: " ++ show sucessfuls
-  when nok $ do
-       putStrLn "No frontend was compiled sucessfully. Giving up."
-       exitWith (ExitFailure 1)
+  mapM_ (precompile pd' lbi verbosity) precompiles
hunk ./Setup.hs 43
-precompile ghc (moduleName, dependencies) = do
+dependencyName (Dependency name _) = name
+
+precompile pd lbi verbosity (moduleName, dependencies) = when ok $ do  
+  -- just pretend that we build a library with the given modules
hunk ./Setup.hs 48
-  exitCode <- rawSystemVerbose 0 ghc (precompArgs ++ map ("-package "++) dependencies ++ [moduleName])
-  when (exitCode /= ExitSuccess) $
-       putStrLn $ "Precompiling failed: " ++ moduleName
-  return (moduleName, exitCode)
+  let [Executable "yi" _ yiBuildInfo] = executables pd
+      pd' = pd {executables = [], 
+                library = Just (Library {exposedModules = [moduleName],
+                                         libBuildInfo = yiBuildInfo})}
+  GHC.build pd' lbi verbosity
+     where availablePackages = map dependencyName $ buildDepends pd
+           ok = all (`elem` availablePackages) dependencies
+                               
hunk ./Setup.hs 61
-               ("Yi.Gtk.UI", ["gtk", "sourceview"]),
-               ("Yi.Dired", ["unix"])]
-
-precompArgs = ["-DGHC_LIBDIR=\"dummy1\"", 
-               "-DYI_LIBDIR=\"dummy2\"", 
-               "-fglasgow-exts", 
-               "-package ghc",
-               "-package filepath",
-               "-cpp",
-               "-Wall",
-               "-hide-all-packages", -- otherwise wrong versions of packages will be picked.
-               "-package base",
-               "-package mtl",
-               "-package regex-compat-0.71",
-               "-package regex-posix-0.71",
-               "-package regex-base-0.72",
-               "--make"]
-               -- please note: These args must match the args given in Yi.Boot
-               -- TODO: factorize.
+               ("Yi.Gtk.UI", ["gtk"]),
+               ("Yi.Dired", [])]
hunk ./Setup.hs 64
-install :: PackageDescription -> LocalBuildInfo -> Maybe UserHooks -> InstallFlags -> IO ()
-install pd lbi hooks bfs = do
+install :: PackageDescription -> LocalBuildInfo -> UserHooks -> InstallFlags -> IO ()
+install pd lbi hooks flags = do
hunk ./Setup.hs 72
-      -- otherwise GHC (via Yi) thinks it has to recompile them.
+      -- otherwise GHC (via Yi) thinks it has to recompile them when Yi is started.
hunk ./Setup.hs 74
-  instHook defaultUserHooks pd' lbi hooks bfs
+  instHook defaultUserHooks pd' lbi hooks flags
hunk ./Yi/Boot.hs 36
-path :: FilePath
-path = GHC_LIBDIR -- See Setup.hs
+ghcLibdir :: FilePath
+ghcLibdir = GHC_LIBDIR -- See Setup.hs
hunk ./Yi/Boot.hs 43
-  -- here we have to make an early choice between vty and gtk.
hunk ./Yi/Boot.hs 46
-  logPutStrLn $ "Using libdir: " ++ libdir
-  session <- GHC.newSession GHC.Interactive (Just path)
+  logPutStrLn $ "Using Yi libdir: " ++ libdir
+  logPutStrLn $ "Using GHC libdir: " ++ ghcLibdir
+  GHC.parseStaticFlags [] -- no static flags for now
+  session <- GHC.newSession (Just ghcLibdir)
+  logPutStrLn $ "Session started!"
hunk ./Yi/Boot.hs 60
+  -- note: These args must match the args given by cabal at pre-compilation, currently this is 
+  -- not done correctly, so sometimes we use a different version of some package here.
+
hunk ./Yi/FastBuffer.hs 42
-import Data.ByteString.Base 
+import Data.ByteString (ByteString)
hunk ./Yi/Interact.hs 445
-
-forever :: Monad m => m a -> m b
-forever f = f >> forever f
hunk ./Yi/Main.hs 93
+-- TODO: pull this out of the cabal configuration
hunk ./cabal-make.inc 20
+cabal_config=dist/setup-config
+
hunk ./cabal-make.inc 108
-configure: .setup-config
+configure: $(cabal_config)
hunk ./cabal-make.inc 110
-build: .setup-config
+build: $(cabal_config)
hunk ./cabal-make.inc 122
+	-./setup clean
hunk ./cabal-make.inc 124
-	rm -f .setup-config .installed-pkg-config ./setup `find . -name '*.hi' -o -name '*.o'`
+	rm -f $(cabal_config) .installed-pkg-config ./setup `find . -name '*.hi' -o -name '*.o'`
hunk ./cabal-make.inc 137
-# LICENSE dependency makes sure the links are created if that is needed.
-setup: mklinks Setup.*hs 
+setup: Setup.*hs 
hunk ./cabal-make.inc 145
-.setup-config: setup *.cabal
+$(cabal_config): setup *.cabal
hunk ./cabal-make.inc 147
-	sed -e 's/\\\\/\//g' < .setup-config > .tmp.setup-config
-	mv .tmp.setup-config .setup-config
-
-# The previous two lines provide a workaround for a strange problem on
-# Windows.  The forward slashes in that file all get changed to
-# backslashes.  The difficulty is that some of those slashes are part of
-# URLs rather than file paths.  The sed & mv restore the back-slashes.
-# This workaround works fine for cygwin.  I haven't tried under msys.
-
hunk ./cabal-make.inc 189
-haddock: .setup-config
+haddock: $(cabal_config)
hunk ./cabal-make.inc 248
-mklinks:
-	test -e LICENSE || ln -sf ../../LICENSE
+
hunk ./yi.cabal 3
+Cabal-Version:  >= 1.2.1
hunk ./yi.cabal 14
-build-depends:  filepath>=1.0, ghc>=6.6, base, mtl, regex-posix==0.71
+
+Flag vty {
+  Description: Precompile vty UI
+  Default:     True
+}
+
+Flag gtk {
+  Description: Precompile gtk UI
+  Default:     True
+}
+
+
+Executable yi {
+build-depends:  array,  base,  bytestring,  containers,  directory,  filepath>=1.0,  ghc>=6.8,  mtl, process, old-locale, old-time,  regex-base>=0.72, regex-compat>=0.71, regex-posix==0.72,  unix
+-- unix dependency should be eventually removed
+
+if flag(vty) {
+  build-depends: vty>=3.0.0
+}
+
+if flag(gtk) {
+  build-depends: gtk>=0.9.12
+}
+
+
hunk ./yi.cabal 42
-executable:     yi
hunk ./yi.cabal 50
-
-
+}
}

Context:

[Oops, non-empty list has length 1. (Thanks Corey)
[EMAIL PROTECTED] 
[Changed handling of up and down in Vim keymap to match expected behavior
[EMAIL PROTECTED]
 In vim moving the cursor up and down a line tries to retain the current column. yi would previously always move the cursor to the start of the line.
] 
[allow for config.mk to set desired version of ghc to use
[EMAIL PROTECTED] 
[Added a completeWordB action to the emacs key bindings, there is no key-binding for it but it should I guess be C-RET, Use it in my own YiConfig though and it's quite nice
[EMAIL PROTECTED] 
[Fixed indent such that when we indent the current line the cursor is kept at the same point in the actual text of the line, which is more intuitive I feel
[EMAIL PROTECTED] 
[Added more exports to the Yi.Keymap.Emacs module such that the user can redefine these keys in their ~/.yi/YiConfig.hs
[EMAIL PROTECTED] 
[added more to the Yi.Keymap.Emacs export list to assist in writing custom keymaps based on the emacs one.
[EMAIL PROTECTED] 
[when we copy (without cutting) the selected region the mark is now unset
[EMAIL PROTECTED] 
[Made cutting and pasting work a little better with the selection, ie it doesn't annoyingly keep the mark set.
[EMAIL PROTECTED] 
[Changed the selected style such that the selection is highlighted, some other movements need a bit of work though.
[EMAIL PROTECTED] 
[Changed the style a little, but more importantly made the Haskell syntax colouring a little more ameinable to configuration by the user
[EMAIL PROTECTED] 
[Fixed Undo such that it does the right thing if the SavedFilePoint is only the only thing in either list, that is it doesn't throw it away.
[EMAIL PROTECTED] 
[Added 'frontend' and 'user' options to MkConfig.hs
[EMAIL PROTECTED] 
[Added a haskell script to generate the config.mk I think this can avoid a lot of users having to continuously say NO when recording stuff, it's kind of annoying.
[EMAIL PROTECTED] 
[remove overhead handling where it's not needed
[EMAIL PROTECTED] 
[incremental parser: nicer test output
[EMAIL PROTECTED] 
[insert at the end of shifted strings, not before.
[EMAIL PROTECTED] 
[Add a testfile for incremental parsers experiments
[EMAIL PROTECTED] 
[incremental parser improvements
[EMAIL PROTECTED] 
[restore printing of action results
[EMAIL PROTECTED] 
[user input are Action(s). fix issue #44
[EMAIL PROTECTED] 
[vastly improve README file
[EMAIL PROTECTED] 
[Updated the empty list so that a newly opened file doesn't have the modified flag
[EMAIL PROTECTED] 
[added saved file point indicators to the undo list
[EMAIL PROTECTED] 
[Clear the undos on saving the file.
[EMAIL PROTECTED] 
[Fix old comment
[EMAIL PROTECTED] 
[remove obsolete cbits directory
[EMAIL PROTECTED] 
[Comments
[EMAIL PROTECTED] 
[Move the Direction type to a better place and rename its constructors
[EMAIL PROTECTED] 
[Extend Action data type
[EMAIL PROTECTED] 
[Introduced the Action datatype
[EMAIL PROTECTED] 
[Fix some bugs in IncrementalParser 2
[EMAIL PROTECTED] 
[Other incremental parser prototype
[EMAIL PROTECTED] 
[Add a prototype for an incremental parser
[EMAIL PROTECTED] 
[Better fallback strategy when trying to load a wrong module. Fixes issue 21.
[EMAIL PROTECTED] 
[Do not use prefix/bin for haddock and HsColour
Jens Petersen <[EMAIL PROTECTED]>**20070722130918] 
[Update HsColour mode to -anchorCSS
Jens Petersen <[EMAIL PROTECTED]>**20070722131142] 
[Add support for Sockets, Block and Character devices and Named Pipes.  Improve dired colours to be more in line with GNU color ls.
Jens Petersen <[EMAIL PROTECTED]>**20070722131438] 
[Put some indent stuff at the BufferM level
[EMAIL PROTECTED] 
[bugfix: don't crash when the cursor is out of sight
[EMAIL PROTECTED] 
[Flip argument order to take advantage of partial applications
[EMAIL PROTECTED] 
[move status line to Editor
[EMAIL PROTECTED] 
[Take IO out of EditorM
[EMAIL PROTECTED] 
[ghc-6.6.1 has regex-base-0.72 not 0.71
Jens Petersen <[EMAIL PROTECTED]>**20070710230729] 
[Comment
[EMAIL PROTECTED] 
[Take IO out of BufferM monad
[EMAIL PROTECTED] 
[remove a usage of unsafePerformIO
[EMAIL PROTECTED] 
[Minor cleanups
[EMAIL PROTECTED] 
[Avoid a use of IO
[EMAIL PROTECTED] 
[Fix warnings
[EMAIL PROTECTED] 
[bugfix: properly create named marks
[EMAIL PROTECTED] 
[Properly ignore invalid updates + simplify
[EMAIL PROTECTED] 
[Fix Makefile and config.mk
[EMAIL PROTECTED] 
[bugfix: gotoLn < 0 moves point to 0 (not eof)
[EMAIL PROTECTED] 
[Don't use Mark for overlays (only MarkValue). This also fixes issue #40
[EMAIL PROTECTED] 
[Minor undo-related cleanups
[EMAIL PROTECTED] 
[gtk: fix the width of the mini-window textview
[EMAIL PROTECTED] 
[Rewrite FastBuffer so it's purely functional
[EMAIL PROTECTED]
 The new implementation uses ByteStrings as storage
 
] 
[Set the default Gtk window size to something reasonable
Jens Petersen <[EMAIL PROTECTED]>**20070705014545] 
[Wrap text by character in Gtk textviews
Jens Petersen <[EMAIL PROTECTED]>**20070705015710] 
[build fix: add missing Buffer.HighLevel
[EMAIL PROTECTED] 
[Shuffle core around: mainly take Buffer-only action out of Core so they can be shared at a lower level
[EMAIL PROTECTED] 
[Move yet more actions to BufferM level
[EMAIL PROTECTED] 
[Move more functions to BufferM level
[EMAIL PROTECTED] 
[Factoring out common indent handling
[EMAIL PROTECTED]
 Factored out common aspects of indent handling from Emacs and Vim.
 The settings for tab expansion etc is stored in a buffer dynamic variable.
 Currently the settings reflect the names of the Vim settings with the same purpose.
 Updated Vim keymap to perform tab expansion.
] 
[Re-tabify Vim keymap
[EMAIL PROTECTED]
 The standard for this file is to expand tabs. Expanded any \t
] 
[fix warnings
[EMAIL PROTECTED] 
[Attempt to fix issue 35: only Alt should generate "Meta"
[EMAIL PROTECTED] 
[isearch: search word on cursor (C-w)
[EMAIL PROTECTED] 
[Add M-! (shell-command) binding to shellCommandE
Jens Petersen <[EMAIL PROTECTED]>**20070701102431] 
[make Buffer and Editor action dynamically available
[EMAIL PROTECTED] 
[Also pre-compile Main.hs (and fix its build)
[EMAIL PROTECTED] 
[Some more core-level cleanups
[EMAIL PROTECTED] 
[Remove more YiM-level buffer stuff
[EMAIL PROTECTED] 
[remove deleteE/deleteNE/killE
[EMAIL PROTECTED] 
[remove insertE/insertNE
[EMAIL PROTECTED] 
[remove atSolE and friends
[EMAIL PROTECTED] 
[remove getPointE/gotoPointE and adapt
[EMAIL PROTECTED] 
[Remove gotoLnE/gotoLnFromE
[EMAIL PROTECTED] 
[Have gotoLnFromE/gotoLnE return the reached line number
[EMAIL PROTECTED] 
[Remove the semantic-devoid nopE
[EMAIL PROTECTED] 
[Move some operations from Core to CoreUI
[EMAIL PROTECTED] 
[Move some Core functions to the Buffer level
[EMAIL PROTECTED] 
[fix compile
[EMAIL PROTECTED] 
[More instances of the YiAction class
[EMAIL PROTECTED] 
[Generalized UnivArgument so it works with the YiAction class
[EMAIL PROTECTED] 
[Remove another spurious #include "YiUtils.h"
[EMAIL PROTECTED] 
[Add function to delete 1 character forward from the current point
[EMAIL PROTECTED] 
[Make BufferM a newtype
[EMAIL PROTECTED] 
[Introduce the YiAction class
[EMAIL PROTECTED]
 
 This will allow to remove all the redefinitions of Buffer-local primitives
 at core-level
] 
[Remove obsolete inclusion of YiUtils.h
[EMAIL PROTECTED] 
[blanks and comments
[EMAIL PROTECTED] 
[vim: improve bindings of window operations
[EMAIL PROTECTED] 
[Add tryCloseE: delete window unless it's the only one
[EMAIL PROTECTED] 
[Fix closeE so quitting in vi(m) mode is possible
[EMAIL PROTECTED] 
[Comment scheduleRefresh implementation
[EMAIL PROTECTED] 
[gtk: change once more the way cursor and focus is handled
[EMAIL PROTECTED]
 
 My first analysis seemed to be correct; see issue 4.
 
 In detail:
 
 left down: place cursor + focus
 left up: place mark + copy
 mid down: place cursor + paste
 
] 
[remove obsolete, useless and broken piece of code
[EMAIL PROTECTED] 
[properly handle mouse cursor move and selection (gtk)
[EMAIL PROTECTED] 
[Allow UI do directly send Editor events into the execution channel
[EMAIL PROTECTED] 
[insert windows below the current window
[EMAIL PROTECTED]
 (so that the mini-window is below the window it refers to)
] 
[bugfix: properly handle the unsetting of mark
[EMAIL PROTECTED] 
[gtk: use a simpler method to focus the correct internal window
[EMAIL PROTECTED] 
[gtk: bugfix: properly focus the window that has been clicked on
[EMAIL PROTECTED] 
[bugfix: correctly set the heights of the GTK windows (so page up/down work)
[EMAIL PROTECTED] 
[Fixes issue 26 and 5: runBuffer is now atomic to prevent race conditions
[EMAIL PROTECTED]
 See: http://code.google.com/p/yi-editor/issues/detail?id=26&can=2&q=#c4
 for reasoning on the cause of the bug and how making runBufer atomic fixes this.
] 
[Makefile update
[EMAIL PROTECTED] 
[Remove the now useless C bits.
[EMAIL PROTECTED] 
[No longer use C startOfLineNr
[EMAIL PROTECTED] 
[Don't use ccountLines any more
[EMAIL PROTECTED] 
[Attempt at computing the height of gtk windows. (failed, but here's the code for reference)
[EMAIL PROTECTED] 
[remove useless directories
[EMAIL PROTECTED] 
[Use same syntax highlighting for gtk frontend.
[EMAIL PROTECTED]
 
 As an added benefit, we no longer depend on SourceView. Hence Yi should be
 compilable on windows.
 
] 
[Initital integrate of yi-lib into Yi
[EMAIL PROTECTED]
 Moved all yi-lib source files into Yi.
 Updated cabal description with additions from yi-lib.
 Extended Setup.hs to:
     - Copy the data files moved from yi-lib
     - The compiled object files to a "cbits" directory under the data file
       installation directory.
 Extented Yi.Boot to load the C object files before compiling the dynamic main.
 Currently there is only one object file: YiUtils.o. This is hard-coded into
 Yi.BaseExternalObjects.
 
 TODO: Dynamically generate BaseExternalObjects
 TODO: Verify the linking of the C object files does not interfere with the
 dynamic reconfigure of Yi.
 TODO: Dynamically compile the C sources in much the same way the rest of 
 Yi is compiled.
 
] 
[Fix warning
[EMAIL PROTECTED] 
[Add tentative Yi logo
[EMAIL PROTECTED] 
[Revert to use plain textview for Gtk UI
[EMAIL PROTECTED] 
[fix some warnings
[EMAIL PROTECTED] 
[Improve the Contributors calculator
[EMAIL PROTECTED] 
[Use active buffer's directory as start for file search
Fraser Wilson <[EMAIL PROTECTED]>**20070621180147
 
 The buffer may not have a directory; in which case we use $home.
 Paths are normalised, and '..' is removed.
] 
[comment fix
[EMAIL PROTECTED] 
[Remove TODO list (subsumed by issue tracking)
[EMAIL PROTECTED] 
[Dynamically load the frontend.
[EMAIL PROTECTED]
 
 * We no longer have a build per frontend
 * Each module is compiled at most once
 * Bits of yi that need specific packages are each pre-compiled separately,
   in an uniform way.
 
] 
[build fix: be more precise about the packages we want (at pre-compile time.)
[EMAIL PROTECTED] 
[build fix: Fastbuffer no longer depends on Vty
[EMAIL PROTECTED] 
[Create the Event channel in the Core instead of each UI
[EMAIL PROTECTED] 
[config.mk and README clarifications
[EMAIL PROTECTED] 
[build fix: do not depend on unreleased version of vty (imgHeight)
[EMAIL PROTECTED] 
[Adding split window support to Vim keymapping
[EMAIL PROTECTED]
 Vim uses the key sequences:
     ^W^W swap focus with previous split
     ^W^S Split current window vertically
 Along with some other two-key window movement and split commands. 
 This patch adds the ^W^S split window action and changes the binding for nextWinE to ^W^W.
 
] 
[Better model for UI implementation
[EMAIL PROTECTED] 
[remove obsolete code
[EMAIL PROTECTED] 
[rename EditorM to YiM in the example config
[EMAIL PROTECTED] 
[More cleanup
[EMAIL PROTECTED] 
[Factor and simplify some buffer-closing related code
[EMAIL PROTECTED] 
[simplify upScreenE and downScreenE
[EMAIL PROTECTED] 
[Make loadE idempotent and get C-x d to load Dired if reqd
[EMAIL PROTECTED] 
[TAG thousand patches
[EMAIL PROTECTED] 
Patch bundle hash:
8d72d655482220418e257dadbed8b418a9e141b8
_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to