Re: [Haskell-cafe] ghc-mtl, hint, mueval for ghc-7.6 ?
Hi Johannes, The repository version of ghc-mtl already compiles with ghc 7.6.1. I'm working at the moment on making hint compile again as well (am I the only one on this list that doesn't get excited with every new release of ghc? :)), then I'll upload both to hackage. Thanks, Daniel On Oct 8, 2012, at 2:21 PM, Johannes Waldmann wrote: > While porting some code to 7.6, I'm stuck here: > > Preprocessing library ghc-mtl-1.0.1.1... > [1 of 1] Compiling Control.Monad.Ghc ( Control/Monad/Ghc.hs, > dist/build/Control/Monad/Ghc.o ) > > Control/Monad/Ghc.hs:29:48: >No instance for (DynFlags.HasDynFlags Ghc) > > this seems to block hint and mueval. > Is there a known workaround for this problem, > or a sugggested replacement package? > > Thanks - J.W. > > > > > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] hint and type synonyms
Hi I think I see now what the problem you observe is. It is not related with type synonyms but with module scoping. Let me briefly discuss what hint is doing behind the scenes and why, this may give a better understanding of what kind of things will and will not work. While hint is directly tied to ghc, it should be possible to implement something similar for any self-hosting Haskell compiler. Essentially, you need the compiler to provide a function compileExpr that given a string with a Haskell expression, returns a value of some type, say CompiledExpr (or an error if the string is not a valid expression, etc). So, for instance, 'compileExpr "not True"' will produce something of type CompiledExpr, but we know that it is safe to unsafeCoerce this value into one of type Bool. Now, what happens if one unsafeCoerces to a Bool the result of running compileExpr on "[True]"? This is, of course, equivalent to running '(unsafeCoerce [True]) :: Bool' and sounds dangerous. Indeed, if your compiler were to keep type information in its CompiledExprs and check for type correctness on each operation (akin to what the interpreters for dynamic languages (like Perl, Ruby, etc.) do) then you may get a gracious runtime error; but most (if not all) of Haskell compilers eliminate all type information from the compiled representation (which is a good thing for performance), so the result of a bad cast like the one above will surely result in an ugly (uninformative) crash. So how does we deal with this in hint? When you write 'interpret "not True" (as :: Bool)' we want a runtime guarantee that "not True" is in fact a value of type Bool. We do this by calling compileExpr with "(not True) :: Bool" instead of just with "not True". This way, an incorrect cast is caught at runtime by compileExpr (e.g. "([True]) :: Bool" will fail to compile). In order to do this, the type parameter must be an instance of Data.Typeable and we use the typeOf function to obtain the type (e.g. show $ Data.Typeable.typeOf "True" == "Bool") This is, as you've noticed, a little fragile. For this to work, the type expression returned by Data.Typeable.typeOf must correspond to something that is visible to the complieExpr function. You do this in hint adding the relevant modules with the setImports function. It may be a little inconvenient, but I think it is unavoidable. I wouldn't ever recommend writing bogus instances of Typeable as in your original example. If you find a situation where this looks as the more sensible thing to do I'd like to know! Also, in the example from Rc43 you cite below, instead of running setImport on HReal.Core.Prelude you need to run setImport on all the modules that are exported by HReal.Core.Prelude (this can be abstracted in a function, I guess). Since I am on this, I'd like to point out that this solution is, sadly, not 100% safe. There is still one way in which things can go wrong and people often trip over this. The problem roughly comes when your program defines a type T on module M and ends up running compileExpr on an expression of type M.T but in a way such that module M gets to be compiled from scratch. When this happens, the type M.T on your program and the type M.T used in compileExpr may end up having two incompatible representations and the unsafeCoerce will lead to a crash. This typically happens when using hint to implement some form of plugin system. Imagine you have a project organized as follows: project/ project/src/M.hs project/src/main.hs project/plugins/P.hs dist/build/M.o dist/build/main.o dist/build/main where M.hs defines T; P.hs imports M and exports a function f :: T; and main.hs imports M and runs an interpreter that sets "src" as the searchPat, loads "plugins/P.hs", interprets "f" as a T and does something with it. Assume dist/build/main is run from the project dir. When hint tries to load "plugins/P.hs" the "import M" will force the compiler to search for module M.hs in project/src and compile it again (just like ghci would do). This can be bad! The robust solution in this case is to put all the definitions that you want to be shared by your program and your dynamically loaded code in a library (and make sure that it is installed before running the program). Hope this helps... Daniel On Mar 31, 2012, at 8:06 PM, Claude Heiland-Allen wrote: > Hi Daniel, cafe, > > On 31/03/12 17:47, Daniel Gorín wrote: >> Could you provide a short example of the code you'd like to write but gives >> you problems? I'm not able to infer it from your workaround alone... > > This problem originally came up on #haskell, where Rc43 had a problem making > a library with a common module that re-exports several other modules: &g
Re: [Haskell-cafe] efficient chop
On Sep 14, 2011, at 5:29 AM, Kazu Yamamoto (山本和彦) wrote: > Hello, > > Of course, I use ByteString or Text for real programming. But I would > like to know whether or not there are any efficient methods to remove > a tail part of a list. > > --Kazu In that case, I would prefer this version, since it is lazier: lazyChop :: String -> String lazyChop s = pref ++ if null s' then [] else (mid_sp ++ lazyChop s') where (pref,sp_suf) = break isSpace s (mid_sp,s') = span isSpace sp_suf By "lazier" I mean: *Main> chopReverse $ "hello world " ++ undefined "*** Exception: Prelude.undefined *Main> chopFoldr $ "hello world " ++ undefined "*** Exception: Prelude.undefined *Main> lazyChop $ "hello world " ++ undefined "hello world*** Exception: Prelude.undefined Daniel ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] ghc-mtl and ghc-7.2.1
Hi Romildo, you can try the darcs version of ghc-mtl [1], I don't know if that will be enough to build lambdabot, though Best, Daniel [1] http://darcsden.com/jcpetruzza/ghc-mtl On Sep 7, 2011, at 1:34 PM, José Romildo Malaquias wrote: > Hello. > > In order to compile ghc-mtl-1.0.1.0 (the latest released version) with > ghc-7.2.1, I would apply the attached patch, which removes any > references to WarnLogMonad. > > ghc-7.2.1 does not have the monad WarnLogMonad anymore. > > As I do not know the details of the GHC api, I am not sure if this is > enough to use ghc-mtl with ghc-7.2.1. > > I want ghc-mtl in order do build lambdabot. > > Any thoughts? > > Romildo > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] External system connections
On Jul 11, 2011, at 10:48 PM, Alistair Bayley wrote: > 12 July 2011 05:49, Michael Snoyman wrote: >> >> As for Bryan's resource-pool: currently I would strongly recommend >> *against* using it for any purpose. It is based on >> MonadCatchIO-transformers[2], which is a subtly broken package. In >> particular, when I tried using it for pool/persistent in the first >> place, I ended up with double-free bugs from SQLite. > > Do you have a reference explaining this brokenness? e.g. a mailing > list message? I wasn't aware of this. Are the other MonadCatchIO-* > packages also broken? > http://www.haskell.org/pipermail/haskell-cafe/2010-October/084890.html ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] generic putback
I think you need to change the type of putback slightly: import Data.IORef putback :: a -> IO a -> IO (IO a) putback a action = do next <- newIORef a return (do r <- readIORef next; writeIORef next =<< action; return r) main = do getChar' <- putback 'a' getChar str <- sequence $ take 10 $ repeat getChar' putStrLn str Thanks, Daniel On May 15, 2011, at 4:33 PM, Sergey Mironov wrote: > Hi Cafe. I wonder if it is possible to write a IO putback function > with following interface > > putback :: a -> IO a -> IO a > putback x io = ??? > > > where io is some action like reading from file or socket. > I want putback to build new action which will return x on first call, > and continue executing io after that. > > Thanks in advance! > Sergey. > > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: All binary strings of a given length
I expect this one to run in constant space: import Data.Bits genbin :: Int -> [String] genbin n = map (showFixed n) [0..2^n-1::Int] where showFixed n i = map (bool '1' '0' . testBit i) [n-1,n-2..0] bool t f b = if b then t else f Daniel On Oct 15, 2010, at 9:43 AM, Eugene Kirpichov wrote: > Actually my ghci doesn't crash for genbin 25 (haven't tried further), > though it eats quite a bit of memory. > How are you going to use these bit strings? Do you need all of them at once? > > 2010/10/15 Aleksandar Dimitrov : >> On Fri, 15 Oct 2010 14:34:42 +0200, rgowka1 wrote: >> >>> Amazing, will never find this in any other languagw. But ghci crashes >>> for bigger input. Like genbin 20. How to scale this function? >> >> Well, "scaling" this isn't really possible, because of its complexity. It >> generates all permutations of a given string with two states for each >> position. In regular languages, this is the language {1,0}^n, n being the >> length of the string. This means that there are 2^n different strings in the >> language. For 20, that's already 1048576 different Strings! Strings are >> furthermore not really the best way to encode your output. Numbers (i.e. >> bytes) would be much better. You could generate them, and only translate >> into strings when needed. >> >> HTH, >> Aleks >> ___ >> Haskell-Cafe mailing list >> Haskell-Cafe@haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > > > -- > Eugene Kirpichov > Senior Software Engineer, > Grid Dynamics http://www.griddynamics.com/ > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] ghc api printing of types
I believe the way is done in hint is something like this (untested): showType t = do -- Unqualify necessary types -- (i.e., do not expose internals) unqual <- GHC.getPrintUnqual return $ GHC.showSDocForUser unqual (GHC.pprTypeForUser False t) -- False means 'drop explicit foralls' Hope that helps Daniel On Jul 4, 2010, at 8:36 AM, Phyx wrote: I was wondering how given a Type I can get a pretty printed type out of it. I’m currently using showSDocUnqual . pprType . snd . tidyOpenType emptyTidyEnv But this has the problem that predicates don’t get printed, anyone know how GHCi does this? Thanks, Phyx ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Using Hint with a socket server
Hi Tom, There is probably more than one way to do this. Did you try using the package hint-server? [1] It has a very simple interface: you start a "server" and obtain a handle; then you can run an interpreter action using the handle. Something like this: > runIn handle (interpret msg (as :: MyType)) This expression has type IO (Either InterpreterError MyType). You can also run an interpreter action in the background. Keep in mind that the ghc-api is not thread safe, though, so you should start only one server and put the handle in an MVar Hope that helps Daniel [1] http://hackage.haskell.org/package/hint-server On Jun 17, 2010, at 6:35 PM, Tom Jordan wrote: I'm trying to receive small segments of Haskell code over a socket, and be able to evaluate them in real time in GHCI. I've already downloaded Hint and have run the test code, and it's working great. I'm also using the socket server code from Ch.27 of "Real World Haskell" and that is working well also. directly below is the function from the socket server code that handles the incoming messages. Instead of doing this: "putStrLn msg"... I want to send whatever is captured in "msg" to the GHC interpreter that is used in the Hint code, something like this: "eval msg". I'm not sure how to combine both of these functionalities to get them to work with each other.. -- A simple handler that prints incoming packets plainHandler :: HandlerFunc plainHandler addr msg = putStrLn msg Below is the full code for the socket server, then below that is "SomeModule" used in the Hint example test below that. -- file: ch27/syslogserver.hs import Data.Bits import Network.Socket import Network.BSD import Data.List type HandlerFunc = SockAddr -> String -> IO () serveLog :: String -- ^ Port number or name; 514 is default -> HandlerFunc -- ^ Function to handle incoming messages -> IO () serveLog port handlerfunc = withSocketsDo $ do -- Look up the port. Either raises an exception or returns -- a nonempty list. addrinfos <- getAddrInfo (Just (defaultHints {addrFlags = [AI_PASSIVE]})) Nothing (Just port) let serveraddr = head addrinfos -- Create a socket sock <- socket (addrFamily serveraddr) Datagram defaultProtocol -- Bind it to the address we're listening to bindSocket sock (addrAddress serveraddr) -- Loop forever processing incoming data. Ctrl-C to abort. procMessages sock where procMessages sock = do -- Receive one UDP packet, maximum length 1024 bytes, -- and save its content into msg and its source -- IP and port into addr (msg, _, addr) <- recvFrom sock 1024 -- Handle it handlerfunc addr msg -- And process more messages procMessages sock -- A simple handler that prints incoming packets plainHandler :: HandlerFunc plainHandler addr msg = putStrLn msg -- main = serveLog "8008" plainHandler module SomeModule(g, h) where f = head g = f [f] h = f import Control.Monad import Language.Haskell.Interpreter main :: IO () main = do r <- runInterpreter testHint case r of Left err -> printInterpreterError err Right () -> putStrLn "that's all folks" -- observe that Interpreter () is an alias for InterpreterT IO () testHint :: Interpreter () testHint = do say "Load SomeModule.hs" loadModules ["SomeModule.hs"] -- say "Put the Prelude, Data.Map and *SomeModule in scope" say "Data.Map is qualified as M!" setTopLevelModules ["SomeModule"] setImportsQ [("Prelude", Nothing), ("Data.Map", Just "M")] -- say "Now we can query the type of an expression" let expr1 = "M.singleton (f, g, h, 42)" say $ "e.g. typeOf " ++ expr1 say =<< typeOf expr1 -- say $ "Observe that f, g and h are defined in SomeModule.hs, " ++ "but f is not exported. Let's check it..." exports <- getModuleExports "SomeModule" say (show exports) -- say "We can also evaluate an expression; the result will be a string" let expr2 = "length $ concat [[f,g],[h]]" say $ concat ["e.g. eval ", show expr1] a <- eval expr2 say (show a) -- say "Or we can interpret it as a proper, say, int value!" a_int <- interpret expr2 (as :: Int) say (show a_int) -- say "This works for any monomorphic type, even for function types" let expr3 = "\\(Just x) -> succ x" say $ "e.g. we interpret " ++ expr
Re: [Haskell-cafe] How efficient is read?
On May 9, 2010, at 12:32 AM, Tom Hawkins wrote: I have a lot of structured data in a program written in a different language, which I would like to read in and analyze with Haskell. And I'm free to format this data in any shape or form from the other language. Could I define a Haskell type for this data that derives the default Read, then simply print out Haskell code from the program and 'read' it in? Would this be horribly inefficient? It would save me some time of writing a parser. -Tom If your types contain infix constructors, the derived Read instances may be almost unusable; see http://hackage.haskell.org/trac/ghc/ticket/1544 ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Hint causes GHCi linker error under Windows
Hi, Martin Do you have a complete example one can use to reproduce this behavior? (preferably a short one! :P) In any case, I'm resending your message to the glasgow-haskell-users list to see if a ghc guru recognize the error message. It is strange that the problem only manifests on Windows Daniel On Dec 11, 2009, at 7:04 AM, Martin Hofmann wrote: The following hint code causes GHCi to crash under Windows: runInterpreter $ loadModules ["SomeModule.hs"] The error message is: GHCi runtime linker: fatal error: I found a duplicate definition for symbol _hs_gtWord64 whilst processing object file C:\Programme\Haskell Platform\2009.2.0.2\ghc-prim-0.1.0.0 HSghc-prim-0.1.0.o This could be caused by: * Loading two different object files which export the same symbol * Specifying the same object file twice on the GHCi command line * An incorrect `package.conf' entry, causing some object to be loaded twice. GHCi cannot safely continue in this situation. Exiting now. Sorry. The problem does not occur under Unix or with a compiled program. IMHO hint tries to start a second instance of GHCi which is not allowed/possible under Windows. If this is the case a more telling error message would be helpful. I used the Haskell Platform, version 2009.2.0.2 under Windows XP. My package.conf is: C:/Programme/Haskell Platform/2009.2.0.2\package.conf: Cabal-1.6.0.3, GHood-0.0.3, GLUT-2.1.1.2, HTTP-4000.0.6, HUnit-1.2.0.3, MonadCatchIO-mtl-0.2.0.0, OpenGL-2.2.1.1, QuickCheck-1.2.0.0, Win32-2.2.0.0, ansi-terminal-0.5.0, ansi-wl-pprint-0.5.1, array-0.2.0.0, base-3.0.3.1, base-4.1.0.0, bimap-0.2.4, bytestring-0.9.1.4, cgi-3001.1.7.1, containers-0.2.0.1, cpphs-1.9, directory-1.0.0.3, (dph-base-0.3), (dph-par-0.3), (dph-prim-interface-0.3), (dph-prim-par-0.3), (dph-prim-seq-0.3), (dph-seq-0.3), extensible-exceptions-0.1.1.0, fgl-5.4.2.2, filepath-1.1.0.2, (ghc-6.10.4), ghc-mtl-1.0.1.0, ghc-paths-0.1.0.6, ghc-prim-0.1.0.0, haddock-2.4.2, haskeline-0.6.2.2, haskell-src-1.0.1.3, haskell-src-exts-1.3.4, haskell98-1.0.1.0, hint-0.3.2.1, hpc-0.5.0.3, html-1.0.1.2, integer-0.1.0.1, mtl-1.1.0.2, network-2.2.1.4, old-locale-1.0.0.1, old-time-1.0.0.2, packedstring-0.1.0.1, parallel-1.1.0.1, parsec-2.1.0.1, pointless-haskell-0.0.1, pretty-1.0.1.0, process-1.0.1.1, random-1.0.0.1, regex-base-0.72.0.2, regex-compat-0.71.0.1, regex-posix-0.72.0.3, rts-1.0, stm-2.1.1.2, syb-0.1.0.1, template-haskell-2.3.0.1, time-1.1.2.4, utf8-string-0.3.6, xhtml-3000.2.0.1, zlib-0.5.0.0 Thanks, Martin ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Problems with Language.Haskell.Interpreter and errors
On Nov 11, 2009, at 5:39 AM, Martin Hofmann wrote: I still have problems and your code won't typecheck on my machine printing the following error: [...] I assume we are using different versions of some packages. Could you please send me the output of your 'ghc-pkg list'. Thanks, Martin Sure. Global: Cabal-1.6.0.3, GLUT-2.1.1.2, HTTP-4000.0.6, HUnit-1.2.0.3, OpenGL-2.2.1.1, QuickCheck-1.2.0.0, array-0.2.0.0, base-3.0.3.1, base-4.1.0.0, bytestring-0.9.1.4, cgi-3001.1.7.1, containers-0.2.0.1, directory-1.0.0.3, (dph-base-0.3), (dph-par-0.3), (dph-prim-interface-0.3), (dph-prim-par-0.3), (dph-prim-seq-0.3), (dph-seq-0.3), editline-0.2.1.0, extensible-exceptions-0.1.1.0, fgl-5.4.2.2, filepath-1.1.0.2, (ghc-6.10.4), ghc-prim-0.1.0.0, haddock-2.4.2, haskell-src-1.0.1.3, haskell98-1.0.1.0, hpc-0.5.0.3, html-1.0.1.2, integer-0.1.0.1, mtl-1.1.0.2, network-2.2.1.2, network-2.2.1.4, old-locale-1.0.0.1, old-time-1.0.0.2, packedstring-0.1.0.1, parallel-1.1.0.1, parsec-2.1.0.1, pretty-1.0.1.0, process-1.0.1.1, random-1.0.0.1, regex-base-0.72.0.2, regex-compat-0.71.0.1, regex-posix-0.72.0.3, rts-1.0, stm-2.1.1.2, syb-0.1.0.1, template-haskell-2.3.0.1, time-1.1.2.4, time-1.1.4, unix-2.3.2.0, xhtml-3000.2.0.1, zlib-0.5.0.0 User: MonadCatchIO-mtl-0.2.0.0, ghc-mtl-1.0.1.0, ghc-paths-0.1.0.5, hint-0.3.2.0, utf8-string-0.3.5. Hope that helps Daniel ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Problems with Language.Haskell.Interpreter and errors
On Sep 30, 2009, at 2:20 AM, Martin Hofmann wrote: Thanks a lot. You ought to be able to add a Control.Monad.CatchIO.catch clause to your interpreter to catch this kind of errors, if you want. I forgot to mention that this didn't work for me either. Thanks for the report! You are welcome. If you come up with a work around or a fix, I would appreciate if you let me know. Cheers, Martin Apologies for a very very very late follow-up on this thread (http://thread.gmane.org/gmane.comp.lang.haskell.cafe/64013 ). It turns out that Control.Monad.CatchIO.catch was the right thing to use; you were probably bitten, just like me, by the fact that "eval" builds a thunk and returns it, but does not execute it. The following works fine for me: import Prelude hiding ( catch ) import Language.Haskell.Interpreter import Control.Monad.CatchIO ( catch ) import Control.Exception.Extensible hiding ( catch ) main :: IO () main = print =<< (runInterpreter (code `catch` handler)) where s= "let lst [a] = a in lst []" code = do setImports ["Prelude"] forceM $ eval s handler (PatternMatchFail _) = return "catched!" forceM :: Monad m => m a -> m a forceM a = a >>= (\x -> return $! x) When run, it prints 'Right "catched!"'. Notice that if you change the line 'forceM $ eval s' by an 'eval s', then the offending thunk is reduced by the print statement and the exception is thrown outside the catch. Hope this helps Daniel ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Problems with Language.Haskell.Interpreter and errors
On Sep 29, 2009, at 8:56 AM, Martin Hofmann wrote: Hi, The API of Language.Haskell.Interpreter says, that 'runInterpreter' runInterpreter :: (MonadCatchIO m, Functor m) => InterpreterT m a -> m (Either InterpreterError a) returns 'Left' in case of errors and 'GhcExceptions from the underlying GHC API are caught and rethrown as this'. What kind of errors do a generate here, why are they not caught by runInterpreter and how can I catch them? I assumed to get a 'Left InterpreterError' from the first and an error in MonadCatchIO in the second. :m +Language.Haskell.Interpreter let estr1 = "let lst [a] = a; lst _ = error \"foo\" in lst []" let estr1 = "let lst [a] = a; in lst []" runInterpreter (setImportsQ [("Prelude", Nothing)] >> eval estr1 ) Right "*** Exception: foo runInterpreter ( eval estr2) Right "*** Exception: :1:101-111: Non-exhaustive patterns in function lst Thanks a lot InterpreterErrors are those that prevent your to-be-interpreted code from "compiling/typechecking". In this case, estr1 is interpreted just fine; but the interpreted value is an exception. So I think Ritght... is ok. You ought to be able to add a Control.Monad.CatchIO.catch clause to your interpreter to catch this kind of errors, if you want. I just tried it and failed, though, so this is probably a bug. I'll try to track it down in more detail. Thanks for the report! Daniel ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] .hi inconsistency bug.
So, if I understand correctly, the interpreter is compiling MainTypes twice? No, the interpreter is trying to compile types that were already compiled by the compiler when building your application. The resulting types are incompatible. Could this be a result of having two outputs (one executable and one library) in my .cabal file? it _does_ compile those things twice... If I create a second cabal file which separates these two different packages, would that fix it? I don't think so. If you already have your application split in library part + executable part, then everything should be fine (as long as the library is installed before running your application). The issue is, the (dynamic) interpreter part of my code is part of the main loop of the program, and is (as far as I can see) inseparable from the rest of the code. What you need to separate is the code you are planning to interpret in runtime. For example, say you have: src/HackMail/Main.hs src/HackMail/Data/Types.hs src/SomePlugin.hs and SomePlugin.hs is loaded by the interpreter, then you may want to reorganize your files like this: src/HackMail/Main.hs src/HackMail/Data/Types.hs plugins/SomePlugin.hs and set the source path to "plugins" directory (using something like unsafeSetGhcOption "-i./plugins", or set [searchPath := ["./ plugins"]], if using the darcs version). Daniel I'll give the cabal thing a try, given the incredible triviality of doing everything with cabal, I should be done testing the solution before I hit the send button... Cabal guys, you rock. Thanks again, Dan. /Joe Daniel Gorín wrote: Hi Just a wild guess but maybe the interpreter is recompiling (in runtime) code that has already been compiled to build your application (in compile-time). This may lead to inconsistencies since a type such as HackMail.Data.Main.Types.Filter may refer to two different (and incompatible) types. To see if this is the case, make sure your "dynamic" code is not located together with your base code (i.e., move it to another directory, and set the src file directory for the interpreter accordingly). Now you may get another runtime error, something along the lines of "Module not found: HackMail.Data.MainTypes". This basically means that you need to make your (already compiled) types available to the interpreter. I think the simplest way is to put all your support types in a package, register it with ghc, link your application to it, and ask the interpreter to use this package (with a "-package " flag). Hope this helps! Daniel On Mar 17, 2009, at 11:52 PM, Joe Fredette wrote: List, I've got this project, source on patch-tag here[1] It's a nice little project, I've got the whole thing roughly working, it compiles okay, everything seems to work, until I try to run it, specifically when I run it in ghci, or when I run the main executable (which uses hint), and look at any type involving my "Email" type, it gives me the following error: Type syonym HackMail.Data.MainTypes.Filter: Can't find interface-file declaration for type constructor or class HackMail.Data.ParseEmail.Email Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error As far as I understand, it wants to find the interface-file declaration for a specific type (Email) exported by the ParseEmail module, all of the exports (I think) are in order. I've tried mucking around with it a bit, but I don't fully understand what the error even means, much less how to fix it. Other relevant info, Email is exported in a roundabout way, namely by importing a module MainTypes, which exports a module Email, which exports a the ParseEmail Module, which exports the datatype Email. The "Filter" delcaration it _actually_ complains about (it's just the first place the email type is invoked) is: type Filter a = ReaderT (Config, Email) IO a nothing particularly special. Any help fixing this is greatly appreciated, I did find this bug report[2] which seems like it might be relevant. But trying to unregister -> cabal clean -> cabal install doesn't fix it. I've also tried manually removing the dist/ folder, and also unregistering the package. Thanks again. /Joe [1] http://patch-tag.com/repo/Hackmail/browse [2] http://hackage.haskell.org/trac/ghc/ticket/2057 ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] .hi inconsistency bug.
Hi Just a wild guess but maybe the interpreter is recompiling (in runtime) code that has already been compiled to build your application (in compile-time). This may lead to inconsistencies since a type such as HackMail.Data.Main.Types.Filter may refer to two different (and incompatible) types. To see if this is the case, make sure your "dynamic" code is not located together with your base code (i.e., move it to another directory, and set the src file directory for the interpreter accordingly). Now you may get another runtime error, something along the lines of "Module not found: HackMail.Data.MainTypes". This basically means that you need to make your (already compiled) types available to the interpreter. I think the simplest way is to put all your support types in a package, register it with ghc, link your application to it, and ask the interpreter to use this package (with a "-package " flag). Hope this helps! Daniel On Mar 17, 2009, at 11:52 PM, Joe Fredette wrote: List, I've got this project, source on patch-tag here[1] It's a nice little project, I've got the whole thing roughly working, it compiles okay, everything seems to work, until I try to run it, specifically when I run it in ghci, or when I run the main executable (which uses hint), and look at any type involving my "Email" type, it gives me the following error: Type syonym HackMail.Data.MainTypes.Filter: Can't find interface-file declaration for type constructor or class HackMail.Data.ParseEmail.Email Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error As far as I understand, it wants to find the interface-file declaration for a specific type (Email) exported by the ParseEmail module, all of the exports (I think) are in order. I've tried mucking around with it a bit, but I don't fully understand what the error even means, much less how to fix it. Other relevant info, Email is exported in a roundabout way, namely by importing a module MainTypes, which exports a module Email, which exports a the ParseEmail Module, which exports the datatype Email. The "Filter" delcaration it _actually_ complains about (it's just the first place the email type is invoked) is: type Filter a = ReaderT (Config, Email) IO a nothing particularly special. Any help fixing this is greatly appreciated, I did find this bug report[2] which seems like it might be relevant. But trying to unregister -> cabal clean -> cabal install doesn't fix it. I've also tried manually removing the dist/ folder, and also unregistering the package. Thanks again. /Joe [1] http://patch-tag.com/repo/Hackmail/browse [2] http://hackage.haskell.org/trac/ghc/ticket/2057 ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] .hi inconsistency bug.
Hi Just a wild guess but maybe the interpreter is recompiling (in runtime) code that has already been compiled to build your application (in compile-time). This may lead to inconsistencies since a type such as HackMail.Data.Main.Types.Filter may refer to two different (and incompatible) types. To see if this is the case, make sure your "dynamic" code is not located together with your base code (i.e., move it to another directory, and set the src file directory for the interpreter accordingly). Now you may get another runtime error, something along the lines of "Module not found: HackMail.Data.MainTypes". This basically means that you need to make your (already compiled) types available to the interpreter. I think the simplest way is to put all your support types in a package, register it with ghc, link your application to it, and ask the interpreter to use this package (with a "-package " flag). Hope this helps! Daniel On Mar 17, 2009, at 11:52 PM, Joe Fredette wrote: List, I've got this project, source on patch-tag here[1] It's a nice little project, I've got the whole thing roughly working, it compiles okay, everything seems to work, until I try to run it, specifically when I run it in ghci, or when I run the main executable (which uses hint), and look at any type involving my "Email" type, it gives me the following error: Type syonym HackMail.Data.MainTypes.Filter: Can't find interface-file declaration for type constructor or class HackMail.Data.ParseEmail.Email Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error As far as I understand, it wants to find the interface-file declaration for a specific type (Email) exported by the ParseEmail module, all of the exports (I think) are in order. I've tried mucking around with it a bit, but I don't fully understand what the error even means, much less how to fix it. Other relevant info, Email is exported in a roundabout way, namely by importing a module MainTypes, which exports a module Email, which exports a the ParseEmail Module, which exports the datatype Email. The "Filter" delcaration it _actually_ complains about (it's just the first place the email type is invoked) is: type Filter a = ReaderT (Config, Email) IO a nothing particularly special. Any help fixing this is greatly appreciated, I did find this bug report[2] which seems like it might be relevant. But trying to unregister -> cabal clean -> cabal install doesn't fix it. I've also tried manually removing the dist/ folder, and also unregistering the package. Thanks again. /Joe [1] http://patch-tag.com/repo/Hackmail/browse [2] http://hackage.haskell.org/trac/ghc/ticket/2057 ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Hint and Ambiguous Type issue
I think you can achieve what you want but you need to use the correct types for it. Remember that when you write: getFilterMainStuff :: Deliverable a => FilePath -> Interpreter (Path, Filter a) the proper way to read the signature is "the caller of getFilterMainStuff is entitled to pick the type of a, as long as it picks an instance of Deliverable". Contrast this with a method declaration in Java where: public Set getKeys() is to be read: "The invoked object may pick the type of the result, as long as it is a subclass of (or implements) Set". When you say that you want "to apply fMain to a (Config, Email) and get back a Deliverable a", I think you mean that fMain picks the type for a (and has to be an instance of Deliverable). There two ways to do this in Haskell: 1) You don't. If you know that your possible Deliverables are just FlatEmail and MaildirEmail, then the idiomatic way of doing this would be to turn Deliverable into an ADT: data Deliverable = FlatEmail | MaildirEmail deriving (Typeable) getFilterMainStuff :: FilePath -> Interpreter (Path, Filter Deliverable) 2) Existential types. If, for some reason, you need your "dynamic code" to be able to define new "deliverables", then you need to use the extension called "existential types". -- using GADT syntax data SomeDeliverable where Wrap :: Deliverable a => a -> SomeDeliverable getFilterMainStuff :: FilePath -> Interpreter (Path, Filter SomeDeliverable) This basically resembles the contract of the Java world: if you run fMain you will get a value of type SomeDeliverable; you can pattern- match it and will get something whose actual type you don't know, but that it is an instance of class Deliverable. See http://www.haskell.org/haskellwiki/Existential_type Good luck! Daniel On Mar 6, 2009, at 2:33 AM, Joseph Fredette wrote: Okay, I think I understand... I got so hung up thinking the error had to be in the Interpreter code, I didn't bother to look in the caller... But every answer breeds another question... The practical reason for inferring fMain as being of type "Deliverable a => Filter a", is to apply it (via runReader) to a (Config, Email) and get back a Deliverable a, then to use the deliverIO method on the result -- my question is, it appears I have to "know" the specific type of a in order to get the thing to typecheck, but in order to use it, I need to not know it... Perhaps, in fact, I'm doing this wrong. Thanks for the help Daniel, everyone... /Joe Daniel Gorín wrote: Ok, so I've pulled the latest version and the error I get now is: Hackmain.hs:70:43: Ambiguous type variable `a' in the constraint: `Deliverable a' arising from a use of `getFilterMainStuff' at Hackmain.hs: 70:43-60 Probable fix: add a type signature that fixes these type variable(s) Function getFilterMainStuff compiles just fine . The offending line is in buildConf and reads: > (inboxL, fMain) <- runUnsafeInterpreter . getFilterMainStuff $ filterMainL The problem is that GHC can't figure out the type of fMain. It infers (Filter a), but doesn't know what is a and therefore how to build a proper dictionary to pass to getFilterMainStuff. Observe that you would get a similar error message if you just defined: > f = show . read I can get it to compile by providing a type annotation for fMain: > (inboxL, fMain) <- runUnsafeInterpreter . getFilterMainStuff $ filterMainL > let _ = fMain :: Filter MaildirEmail So once you use fMain somewhere and GHC can infer it's type, everything should work fine. Daniel On Mar 5, 2009, at 11:26 PM, Joseph Fredette wrote: Oh, crap- I must have never pushed the latest patches, I did put the typeable instances in all the appropriate places. And provided a (maybe incorrect? Though I'm fairly sure that shouldn't affect the bug I'm having now) Typeable implementation for Reader, but I still get this ambiguous type. I'll push the current version asap. Thanks. /Joe Daniel Gorín wrote: Hi I've downloaded Hackmain from patch-tag, but I'm getting a different error. The error I get is: Hackmain.hs:63:10: No instance for (Data.Typeable.Typeable2 Control.Monad.Reader.Reader) arising from a use of `interpret' at Hackmain.hs:63:10-67 Hint requires the interpreted values to be an instance of Typeable in order to check, in runtime, that the interpreted value matches the type declared at compile. Therefore, you need to make sure that (Filter a) is indeed an instance of Typeable. Since you have Filter a = Reader (Config, Email) a, you probably need to - Derive Config and Email instances for Filter, - Manually provide Typeable instances for Reader a b, s
Re: [Haskell-cafe] Hint and Ambiguous Type issue
Ok, so I've pulled the latest version and the error I get now is: Hackmain.hs:70:43: Ambiguous type variable `a' in the constraint: `Deliverable a' arising from a use of `getFilterMainStuff' at Hackmain.hs: 70:43-60 Probable fix: add a type signature that fixes these type variable(s) Function getFilterMainStuff compiles just fine . The offending line is in buildConf and reads: > (inboxL, fMain) <- runUnsafeInterpreter . getFilterMainStuff $ filterMainL The problem is that GHC can't figure out the type of fMain. It infers (Filter a), but doesn't know what is a and therefore how to build a proper dictionary to pass to getFilterMainStuff. Observe that you would get a similar error message if you just defined: > f = show . read I can get it to compile by providing a type annotation for fMain: > (inboxL, fMain) <- runUnsafeInterpreter . getFilterMainStuff $ filterMainL > let _ = fMain :: Filter MaildirEmail So once you use fMain somewhere and GHC can infer it's type, everything should work fine. Daniel On Mar 5, 2009, at 11:26 PM, Joseph Fredette wrote: Oh, crap- I must have never pushed the latest patches, I did put the typeable instances in all the appropriate places. And provided a (maybe incorrect? Though I'm fairly sure that shouldn't affect the bug I'm having now) Typeable implementation for Reader, but I still get this ambiguous type. I'll push the current version asap. Thanks. /Joe Daniel Gorín wrote: Hi I've downloaded Hackmain from patch-tag, but I'm getting a different error. The error I get is: Hackmain.hs:63:10: No instance for (Data.Typeable.Typeable2 Control.Monad.Reader.Reader) arising from a use of `interpret' at Hackmain.hs:63:10-67 Hint requires the interpreted values to be an instance of Typeable in order to check, in runtime, that the interpreted value matches the type declared at compile. Therefore, you need to make sure that (Filter a) is indeed an instance of Typeable. Since you have Filter a = Reader (Config, Email) a, you probably need to - Derive Config and Email instances for Filter, - Manually provide Typeable instances for Reader a b, something along the lines of: instance (Typeable a, Typeable b) => Typeable (Reader a b) where... (I don't know why this isn't done in the mtl) - Change the signature to: getFilterMain :: (Typeable a, Deliverable a) => FilePath -> Interpreter (Filter a) Also, you can try using "infer" instead of "as :: " Hope that helps Daniel On Mar 5, 2009, at 8:47 PM, Joseph Fredette wrote: So, I tried both of those things, both each alone and together. No dice. Same error, so I reverted back to the original. :( However, I was, after some random type signature insertions, able to convert the problem into a different one, via: getFilterMain :: Deliverable a => FilePath -> Interpreter (Filter a) getFilterMain MainLoc = do loadModules [fMainLoc]; setTopLevelModules [(takeWhile (/ ='.') fMainLoc)] fMain <- (interpret "(filterMain)" infer) return (fMain :: Deliverable a => Filter a) Inferred type is less polymorphic than expected Quantified type variable `a' is mentioned in the environment: fMain :: Filter a (bound at Hackmain.hs:77:1) In the first argument of `return', namely `(fMain :: (Deliverable a) => Filter a)' In the expression: return (fMain :: (Deliverable a) => Filter a) In the expression: do loadModules [fMainLoc] setTopLevelModules [(takeWhile (/= '.') fMainLoc)] fMain <- (interpret "(filterMain)" infer) return (fMain :: (Deliverable a) => Filter a) I'm thinking that this might be more easily solved -- I do think I understand the issue. somehow, I need to tell the compiler that the 'a' used in the return statement (return (fMain :: ...)) is the same as the 'a' in the type sig for the whole function. While I ponder this, and hopefully receive some more help -- thanks again Dan, Ryan -- Are there any other options besides Hint that might -- at least in the short term -- make this easier? I'd really like to finish this up. I'm _so_ close to getting it done. Thanks, /Joe Ryan Ingram wrote: So, by using the Haskell interpreter, you're using the not-very-well-supported dynamically-typed subset of Haskell. You can tell this from the type signature of "interpret": interpret :: Typeable a => String -> a -> Interpreter a as :: Typeable a => a as = undefined (from http://hackage.haskell.org/packages/archive/hin
Re: [Haskell-cafe] Hint and Ambiguous Type issue
Hi I've downloaded Hackmain from patch-tag, but I'm getting a different error. The error I get is: Hackmain.hs:63:10: No instance for (Data.Typeable.Typeable2 Control.Monad.Reader.Reader) arising from a use of `interpret' at Hackmain.hs:63:10-67 Hint requires the interpreted values to be an instance of Typeable in order to check, in runtime, that the interpreted value matches the type declared at compile. Therefore, you need to make sure that (Filter a) is indeed an instance of Typeable. Since you have Filter a = Reader (Config, Email) a, you probably need to - Derive Config and Email instances for Filter, - Manually provide Typeable instances for Reader a b, something along the lines of: instance (Typeable a, Typeable b) => Typeable (Reader a b) where... (I don't know why this isn't done in the mtl) - Change the signature to: getFilterMain :: (Typeable a, Deliverable a) => FilePath -> Interpreter (Filter a) Also, you can try using "infer" instead of "as :: " Hope that helps Daniel On Mar 5, 2009, at 8:47 PM, Joseph Fredette wrote: So, I tried both of those things, both each alone and together. No dice. Same error, so I reverted back to the original. :( However, I was, after some random type signature insertions, able to convert the problem into a different one, via: getFilterMain :: Deliverable a => FilePath -> Interpreter (Filter a) getFilterMain MainLoc = do loadModules [fMainLoc]; setTopLevelModules [(takeWhile (/='.') fMainLoc)] fMain <- (interpret "(filterMain)" infer) return (fMain :: Deliverable a => Filter a) Inferred type is less polymorphic than expected Quantified type variable `a' is mentioned in the environment: fMain :: Filter a (bound at Hackmain.hs:77:1) In the first argument of `return', namely `(fMain :: (Deliverable a) => Filter a)' In the expression: return (fMain :: (Deliverable a) => Filter a) In the expression: do loadModules [fMainLoc] setTopLevelModules [(takeWhile (/= '.') fMainLoc)] fMain <- (interpret "(filterMain)" infer) return (fMain :: (Deliverable a) => Filter a) I'm thinking that this might be more easily solved -- I do think I understand the issue. somehow, I need to tell the compiler that the 'a' used in the return statement (return (fMain :: ...)) is the same as the 'a' in the type sig for the whole function. While I ponder this, and hopefully receive some more help -- thanks again Dan, Ryan -- Are there any other options besides Hint that might -- at least in the short term -- make this easier? I'd really like to finish this up. I'm _so_ close to getting it done. Thanks, /Joe Ryan Ingram wrote: So, by using the Haskell interpreter, you're using the not-very-well-supported dynamically-typed subset of Haskell. You can tell this from the type signature of "interpret": interpret :: Typeable a => String -> a -> Interpreter a as :: Typeable a => a as = undefined (from http://hackage.haskell.org/packages/archive/hint/0.2.1/doc/html/src/Language-Haskell-Interpreter-GHC.html) In particular, the "as" argument to interpret is specifying what type you want the interpreted result to be typechecked against; the interpretation fails if it doesn't match that type. But you need the result type to be an instance of Typeable; (forall a. Deliverable a => Filter a) most certainly is not. Off the top of my head, you have a couple of directions you can take this. (1) Make Typeable a superclass of Deliverable, saying that all deliverable things must be dynamically typeable. Then derive Typeable on Filter, and have the result be of type "Filter a" using ScopedTypeVariables as suggested before. (You can also pass "infer" to the interpreter and let the compiler try to figure out the result type instead of passing (as :: SomeType).) (2) Make a newtype wrapper around Filter and give it an instance of Typeable, and add a constraint to filterMain that the result type in the filter is also typeable. Then unwrap the newtype after the interpreter completes. Good luck; I've never tried to use the Haskell interpreter before, so I'm curious how well it works and what problems you have with it! -- ryan 2009/3/5 Joseph Fredette : I've been working on a little project, and one of the things I need to do is dynamically compile and import a Haskell Source file containing filtering definitions. I've written a small monad called Filter which is simply: type Filter a = Reader (Config, Email) a To encompass all the email filtering. The method I need to import, filterMain, has type: filterMain :: Deliverable a => Filter a where Deliverable is a type class which abstracts over delivery to a path in the file system. The notion is that I ca
Re: [Haskell-cafe] Newtype deriving with functional dependencies
On Feb 2, 2009, at 1:06 AM, Louis Wasserman wrote: Is there any sensible way to make newtype FooT m e = FooT (StateT Bar m e) deriving (MonadState) work to give instance MonadState Bar (FooT m e)? That is, I'm asking if there would be a semantically sensible way of modifying GeneralizedNewtypeDeriving to handle multi-parameter type classes when there is a functional dependency involved, assuming by default that the newtype is the more general of the types, perhaps? Louis Wasserman wasserman.lo...@gmail.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe did you try this? newtype FooT m e = FooT (StateT Bar m e) deriving (Monad, MonadState Bar)___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] propogation of Error
i would expect to get back the Error from the *first* function in the sequence of functions in checkHeader (oggHeaderError from the oggHeader function). but instead i always see the Error from the *last* function in the sequence, OggPacketFlagError from the OggPacketFlag function. why is this? is there any way i can get the desired behavior...i.e. see the Error from the first function in the sequence that fails? Hi You are essentially asking why this function: checkHeader handle = ((oggHeader handle) >> (oggStreamFlag handle) >> (oggHeaderFlag handle) >> (skipBytes handle 20)>> (oggPageSecCount handle) >> (oggPacketFlag handle)) returns the last error (OggPacketFlagError) instead of the first one. Some type annotations might help you see what is going on. So let's ask ghci the type of, e.g. oggHeaderFlag *File.Ogg> :t oggHeaderFlag oggHeaderFlag :: SIO.Handle -> IO (Either OggParseErrorType [Char]) oggHeaderFlag takes a handle, and computes either an error or a string. But since you are using >>, the computed value is not passed to the next function in the pipe! There is no way checkHeader can stop early simply because it is ignoring the intermediate results altogether. Since you are importing Control.Monad.Error, I believe you would probably want oggHeaderFlag et al to have type: SIO.Handle -> ErrorT OggParseErrorType IO [Char] This will propagate errors correctly. You can see a version of your code using ErrorT here: http://hpaste.org/12705#a1 Daniel ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] using ghc as a library
On Oct 25, 2008, at 8:39 PM, Anatoly Yakovenko wrote: so I am trying to figure out how to use ghc as a library. following this example, http://www.haskell.org/haskellwiki/GHC/As_a_library, i can load a module and examine its symbols: [...] given Test.hs: module Test where hello = "hello" world = "world" one = 1 two = 2 i get this output: $ ./Main ./Test.hs "[]" "[Test.hello, Test.one, Test.two, Test.world]" which is what i expect. My question is, how do manipulate the symbols exported by Test? Is there a way to test the types? lets say i wanted to sum all the numbers and concatenate all the strings in Test.hs, how would i do that? Hi, Anatoly Sorry for don't answering your question in the first place, but for this kind of tasks I believe you might be better off using some lightweight wrapper of the GHC Api. For instance, using http://hackage.haskell.org/cgi-bin/hackage-scripts/package/hint you write: import Language.Haskell.Interpreter.GHC import Control.Monad.Trans ( liftIO ) import Control.Monad ( filterM ) test_module = "Test" main :: IO () main = do s <- newSession withSession s $ do loadModules [test_module]-- loads Test.hs... setTopLevelModules [test_module] -- ...and puts it in scope setImports ["Prelude"] -- put the Prelude in scope too -- exports <- getModuleExports "Test" -- get Test's symbols let ids = [f | Fun f <- exports] -- strings <- filterM (hasType "[Char]") ids conc <- concat `fmap` mapM (\e -> interpret e infer) strings liftIO $ putStrLn conc -- ns <- filterM (hasType "Integer") ids sum_ns <- sum `fmap` mapM (\e -> interpret e (as :: Integer)) ns liftIO $ putStrLn (show sum_ns) hasType :: String -> Id -> Interpreter Bool hasType t e = do type_of_e <- typeOf e return (type_of_e == t) $ ./Main helloworld 3 The version in hackage of hint works only with GHC 6.6.x and 6.8.x, mind you, but a new version is coming soon Good luck, Daniel ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Haskell's type system
On Jun 17, 2008, at 11:08 PM, Don Stewart wrote: Haskell's type system is based on System F, the polymorphic lambda calculus. By the Curry-Howard isomorphism, this corresponds to second-order logic. just nitpicking a little this should read "second-order propositional logic", right? daniel ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] hint / ghc api and reloading modules
(Since this can be of interest to those using the ghc-api I'm cc-ing the ghc users' list.) Hi, Evan The odd behavior you spotted happens only with hint under ghc-6.8. It turns out the problem was in the session initialization. Since ghc-6.8 the newSession function no longer receives a GhcMode. The thing is that, apparently, if one was passing the Interactive mode to newSession under ghc-6.6, now you ought to set the ghcLink dynflag to LinkInMemory instead. I couldn't find this documented anywhere (except for this patch http://www.haskell.org/pipermail/cvs-ghc/2007-April/034974.html) but it is what ghci is doing and after patching hint to do this the reloading of modules works fine. I'll be uploading a fixed version of hint to hackage in the next days. Thanks, Daniel On May 31, 2008, at 2:46 PM, Evan Laforge wrote: I'm using "hint", but since it's basically a thin wrapper around the GHC API, this is probably a GHC api question too. Maybe this should go to cvs-ghc? Let me know and I'll go subscribe over there. It's my impression from the documentation that I should be able to load a module interpreted, make changes to it, and then reload it. This is, after all what ghci does. It's also my impression that the other imported modules should be loaded as object files, if the .hi and .o exist, since this is also what ghci does. However, if I load a module and run code like so (using hint): GHC.loadModules ["Cmd.LanguageEnviron"] GHC.setTopLevelModules ["Cmd.LanguageEnviron"] GHC.setImports ["Prelude"] cmd_func <- GHC.interpret (mangle_code text) (GHC.as :: LangType) It works fine until I change LanguageEnviron. If I make a change to a function, I don't see my changes in the output, as if the session is only getting partially reset. If I insert a syntax error, then I do see it, so it is recompiling the file in some way. However, if I *rename* the function and call it with the new name, I get a GhcException: During interactive linking, GHCi couldn't find the following symbol: ... etc. So I examined the code in hint for loadModules and the code in ghci/InteractiveUI.hs:/loadModule, and they do look like they're doing basically the same things, except a call to rts_revertCAFs, which I called too just for good measure but it didn't help (I can't find its source anywhere, but the ghci docs imply it's optional, so I suspect it's a red herring). Here's a condensed summary of what hint is doing: -- reset GHC.setContext session [] [] GHC.setTargets session [] GHC.load session GHC.LoadAllTargets -- rts_revertCAFs -- load targets <- mapM (\f -> GHC.guessTarget f Nothing) fs GHC.setTargets session targets GHC.load session GHC.LoadAllTargets -- interpret let expr_typesig = "($expr) :: xyz" expr_val <- GHC.compileExpr session expr_typesig return (GHC.Exts.unsafeCorce# expr_val :: a) -- GHC.compileExpr maybe_stuff <- hscStmt hsc_env ("let __cmCompileExpr = "++expr) ([n],[hv]) <- (unsafeCoerce# hval) :: IO [HValue] return (Just hv) and then ghci does: -- load GHC.setTargets session [] GHC.load session LoadAllTargets targets <- io (mapM (uncurry GHC.guessTarget) files') GHC.setTargets session targets GHC.load session LoadAllTargets rts_revertCAFs putStrLn "Ok, modules loaded: $modules" -- interpret GHC.runStmt session stmt step -- GHC.runStmt Just (ids, hval) <- hscStmt hsc_env' expr coerce hval to (IO [HValue]) and run it carefully So it *looks* like I'm doing basically the same thing as ghci... except obviously I'm not because ghci reloads modules without any trouble. Before I go start trying to make hint even more identical to ghci, is there anything obviously wrong here that I'm doing? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Problem with Python AST
Hi Something like this would do? if_ = Compound $ If [(IntLit 6, Suite [] [Break])] Nothing while_ = Compound $ While (IntLit 6) (Suite [] [if_]) Nothing f = Program [while_] -- this one fails -- f2 = Program [if_] newtype Ident = Id String data BinOp = Add | Sub data Exp = IntLit Integer | BinOpExp BinOp Exp Exp data NormalCtx data LoopCtx data Statement ctx where Compound :: Compound ctx -> Statement ctx Pass :: Statement ctx Break:: Statement LoopCtx newtype Global = Global [Ident] data Suite ctx = Suite [Global] [Statement ctx] type Else ctx = Suite ctx data Compound ctx where If:: [(Exp, Suite ctx)] -> Maybe (Else ctx) -> Compound ctx While :: Exp -> (Suite LoopCtx) -> Maybe (Else LoopCtx) -> Compound ctx newtype Program = Program [Statement NormalCtx] Daniel On Feb 20, 2008, at 5:12 PM, Roel van Dijk wrote: Hello everyone, I am trying to create an AST for Python. My approach is to create a data type for each syntactic construct. But I am stuck trying to statically enforce some constraints over my statements. A very short example to illustrate my problem: newtype Ident = Id String data BinOp = Add | Sub data Exp = IntLit Integer | BinOpExp BinOp Exp Exp data NormalCtx data LoopCtx data Statement ctx where Compound :: Compound -> Statement ctx Pass :: Statement ctx Break:: Statement LoopCtx newtype Global = Global [Ident] data Suite ctx = Suite [Global] [Statement ctx] type Else = Suite NormalCtx data Compound = If [(Exp, Suite NormalCtx)] (Maybe Else) | While Exp (Suite LoopCtx) (Maybe Else) newtype Program = Program [Statement NormalCtx] The "global" statement makes an identifier visible in the local scope. It holds for the entire current code block. So it also works backwards, which is why I didn't make it a statement but part of a suite (= block of statements). Some statements may occur in any context, such as the "pass" statement. But others are only allowed in certain situations, such as the "break" statement. This is why I defined the Statement as a GADT. I just supply the context in which the statement may be used and the typechecker magically does the rest. Feeling very content with this solution I tried a slightly more complex program and discovered that my AST can not represent this Python program: for i in range(10): if i == 6: break The compound if statement is perfectly valid nested in the loop because the Compound constructor of Statement allows any context. But the suites inside the clauses of the if statement only allow normal contexts. Since Break has a LoopCtx the typechecker complains. Is there some other way to statically enforce that break statements can only occur _nested_ inside a loop? There is a similar problem with return statements that may only occur in functions. These nested statements should somehow 'inherit' a context, if that makes any sense :-) I know I can simply create separate data types statements that can occur inside loops and function bodies. But that would make the AST a lot more complex, something I try to avoid. Python's syntax is already complex enough! Most of these constraints are not in the EBNF grammar which can be found in the language reference, but they are specified in the accompanying text. The cpython interpreter will generate SyntaxError's when you violate these constraints. See also Python's language reference: http://docs.python.org/ref/ref.html (see sections 6 and 7) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe