Re: [Haskell-cafe] Hint causes GHCi linker error under Windows

2009-12-14 Thread Martin Hofmann
Hi Daniel, Do you have a complete example one can use to reproduce this behavior? (preferably a short one! :P) With this code I could reproduce it in ghci. runInterpreter $ loadModules [(SomeModule.hs, Nothing)] Currently I am not on a Windows machine, so I can't tell you if this only

Re: [Haskell-cafe] Hint causes GHCi linker error under Windows

2009-12-14 Thread Martin Hofmann
The following module reproduces the error when loaded into ghci and main is executed under Windows. It works fine when compiled. \begin{code} module Main where import Language.Haskell.Interpreter main = putStrLn File to load: getLine = erroneousLoad erroneousLoad :: FilePath - IO ()

[Haskell-cafe] Hint causes GHCi linker error under Windows

2009-12-11 Thread Martin Hofmann
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

Re: [Haskell-cafe] Problems with Language.Haskell.Interpreter and errors

2009-11-11 Thread Martin Hofmann
I still have problems and your code won't typecheck on my machine printing the following error: Test.hs:9:34: No instance for (Control.Monad.CatchIO.MonadCatchIO (InterpreterT IO)) arising from a use of `catch' at Test.hs:9:34-53 Possible fix: add an

Re: [Haskell-cafe] Problems with Language.Haskell.Interpreter and errors

2009-11-11 Thread Martin Hofmann
Thanks, using MonadCatchIO-mtl-0.2.0.0 and hint-0.3.2.0 did it. ___ 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

2009-11-10 Thread Martin Hofmann
Although late, still very much appreciated. Thanks a lot! Cheers, Martin ___ 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

2009-09-30 Thread Martin Hofmann
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

[Haskell-cafe] Problems with Language.Haskell.Interpreter and errors

2009-09-29 Thread Martin Hofmann
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

Re: [Haskell-cafe] lazy data structure for best-first search

2009-07-07 Thread Martin Hofmann
Thanks Dan, that gave me some new input I can continue working on. Cheers, Martin Am Dienstag, den 07.07.2009, 10:18 -0700 schrieb Dan Piponi: On Wed, Jun 24, 2009 at 6:53 PM, Martin Hofmannmartin.hofm...@uni-bamberg.de wrote: I am looking for a good (preferably lazy) way to implement some

[Haskell-cafe] lazy data structure for best-first search

2009-06-24 Thread Martin Hofmann
I am looking for a good (preferably lazy) way to implement some kind of best-first search. The problem is, the expansion of the 'best' node in the search space forces other 'inferior' nodes to expand too. So my function expand :: Node - ([Node],(Node - [Node])) does not only return some

Re: [Haskell-cafe] lazy data structure for best-first search

2009-06-24 Thread Martin Hofmann
Thanks for the quick and short answer. Maybe I am already thinking too complicated. However, exactly your given preconditions I can not satisfy. The preconditions for bestFirst rate edges xs are: map rate xs must be nondecreasing, Here lies my problem, because edges must also be applied to

[Haskell-cafe] conflicting variable definitions in pattern

2009-05-15 Thread Martin Hofmann
It is pretty clear, that the following is not a valid Haskell pattern: foo (x:x:xs) = x:xs My questions is _why_ this is not allowed. IMHO, the semantics should be clear: The pattern is expected to succeed, iff 'x' is each time bound to the same term. Isn't this allowed, because this would

[Haskell-cafe] ANN: AAIP Workshop on ICFP Deadline Extension

2009-05-12 Thread Martin Hofmann
AAIP Workshop on ICFP Deadline Extension Please note that the submission deadline for the 3rd Workshop on Approaches and Applications of Inductive Programming has been extended to May 25. The workshop takes place for the first time at the 14th ACM SIGPLAN International Conference on Functional

[Haskell-cafe] Who generates Haskell code and uses type information at runtime?

2009-03-18 Thread Martin Hofmann
I try to modify Haskell code, parsed from an external source, at runtime. Therefore I need type information about this code. Sometimes to this is referred to as treating data as code and code as data. In homoiconic languages such as Lisp this would be less cumbersome, but in Haskell this seems to

Re: [Haskell-cafe] Who generates Haskell code and uses type information at runtime?

2009-03-18 Thread Martin Hofmann
GHC is the current state of the art, which will give you a full Haskell AST enriched with type information. You can then just modify the AST directly. I experimented with the AST from HscTypes.CoreModule in the ghc api. However, it seems that this representation is too far away from my

Re: [Haskell-cafe] How to get a typed (type tagged) AST from GHC's core [Was: Dynamically typing TH.Exp at runtime]

2009-03-16 Thread Martin Hofmann
Matthijs Kooijman wrote: I've been working on parsing core in the past few months. For an example, look here: http://git.stderr.nl/gitweb?p=matthijs/projects/fhdl.git;a=blob;f=Translator.hs;h=8072f85925ad1238 The loadModule and findBind functions are interesting. As for iterating the

Re: [Haskell-cafe] How to get a typed (type tagged) AST from GHC's core [Was: Dynamically typing TH.Exp at runtime]

2009-03-16 Thread Martin Hofmann
Okay, many thanks. That's exactly I need (I hope :-) ). Cheers, Martin ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Dynamically typing TH.Exp at runtime

2009-03-13 Thread Martin Hofmann
Sorry, maybe it I didn't made it clear enough. Perhaps I'm misunderstanding something, but since one can infer types in GHCI, that implies one can infer types in the GHC API; since Hint wraps the GHC API, that implies one can infer types in Hint, doesn't it? And indeed, there are functions to

[Haskell-cafe] Re: Typing Dynamic Typing [Was: Dynamically typing TH.Exp at runtime]

2009-03-13 Thread Martin Hofmann
Thanks a lot for the detailed answer. I must admit, I haven't understood it completely yet, so please excuse for probably naive questions. As far as I see from the language defined in Incope.hs, there is only support for the defined primitive functions (add, mult, if_, etc.). Using additional

[Haskell-cafe] How to get a typed (type tagged) AST from GHC's core [Was: Dynamically typing TH.Exp at runtime]

2009-03-13 Thread Martin Hofmann
Brandon S. Allbery KF8NH wrote: I'm pretty sure you can pull a typed AST out of ghc-api and query the type of any node. Thanks. I am relieved to hear that. Could anybody tell me, where to start in the ghc-api? It's pretty hard, when you don't know where to look. Hoogle doesn't know anything

[Haskell-cafe] Dynamically typing TH.Exp at runtime

2009-03-12 Thread Martin Hofmann
I am doing meta-programming at runtime. So my program gets a full Haskell declaration in expression quotation ([d|...|]) modifies it and returns the modified expression. Therefore, I need type information of this expression, and any subexpression, at _runtime_ ! For example: [d| reverse x1 = y1

Re: [Haskell-cafe] Dynamically typing TH.Exp at runtime

2009-03-12 Thread Martin Hofmann
at runtime help? On Mar 12, 2009, at 12:37 PM, Martin Hofmann wrote: I am doing meta-programming at runtime. So my program gets a full Haskell declaration in expression quotation ([d|...|]) modifies it and returns the modified expression. Therefore, I need type information

[Haskell-cafe] Why does instance Ord Pat causes loop

2008-12-08 Thread Martin Hofmann
I am storing the TH data types 'Exp' and 'Pat' in Maps and Sets. As a first attempt to quickly get rid of typechecker's complaints I defined some naive instances of Ord for Exp and Pat. Now it took me about a week to realise, that 'instance Ord Pat' causes ghc to loop. Apparently, there is a

Re: [Haskell-cafe] Why does instance Ord Pat causes loop

2008-12-08 Thread Martin Hofmann
Thanks a lot for the quick replies. Indeed that was not clear to me. Cheers, Martin ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: What causes loop?

2008-12-03 Thread Martin Hofmann
I was not sure about it, so I just speculated. Anyway, thanks a lot. martin ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] What causes loop?

2008-12-02 Thread Martin Hofmann
I've already posted this mail on haskell-cafe, but apparently the subject suggested a too simple question, so I try it here again. I am picking up a discussion with the same topic from haskell-users on 8th November. Thunks with reference on themselves was mentioned as main reason for loop. A

[Haskell-cafe] What causes loop?

2008-12-01 Thread Martin Hofmann
I am picking up a discussion with the same topic from haskell-users on 8th November. Thunks with reference on themselves was mentioned as main reason for loop. A safe recursive definition would be let x = Foo (x+1) However, if you leave out the constructor, let x = x + 1 you get a loop

Re: [Haskell-cafe] code generation

2008-11-04 Thread Martin Hofmann
Sorry for referring to a post, a bit ago. http://www-users.cs.york.ac.uk/~ndm/derive/ (Deriving Generic Functions by Example). Thanks for the pointer, it was already on my to-read-pile :-) I think using Template Haskell for your work would fit very nicely, so is a good choice to learn :-)

[Haskell-cafe] code generation

2008-10-21 Thread Martin Hofmann
We try to learn functional programs from examples, but our system is not yet ported to Haskell, though we are working on it. However, we thought about using TH. Do you have any pointers to papers, etc. ? You'll find our project, system and papers here:

Re: [Haskell-cafe] Associated Types and several Classes

2008-10-14 Thread Martin Hofmann
Hi Ryan. Thanks a lot, that was exactly the information I needed. Concerning the type classes, there are methods, but I dropped them, because they were not necessary for the problem. However, you are right. Implementation hiding is what I need. One suggestion. Maybe a HaskellWiki page on design

Re: [Haskell-cafe] Haskell in Artificial Intelligence

2008-10-13 Thread Martin Hofmann
Hi Christos, We and a colleague from Japan use Haskell for Inductive Functional Programming, i.e. learn programs from examples. However, we just have started to port our program to Haskell: http://www.cogsys.wiai.uni-bamberg.de/effalip/ Susumu Katayama has already a Haskell library:

[Haskell-cafe] Associated Types and several Classes

2008-10-13 Thread Martin Hofmann
{-# OPTIONS_GHC -fglasgow-exts #-} module Test where import qualified Data.Set as S Hi. I try to model the following: Hypotheses are build up from Rules, which itself are made of the type Rule. Because I may change the implementation later, I want to use type classes, which define the

Re: [Haskell-cafe] Prompt Monad

2008-08-15 Thread Martin Hofmann
I am working on a system to induce recursive functional programs from examples, e.g. 'learn' the reverse function from rev [] = [] rev [a] = [a] rev [a,b] = [b,a] rev [a,b,c] = [c,b,a] ... Although I use analytical

Re: [Haskell-cafe] Prompt Monad

2008-08-13 Thread Martin Hofmann
On Tue, Aug 12, 2008 at 5:50 AM, Martin Hofmann [EMAIL PROTECTED] wrote: I just came across last year's thread about Ryan Ingram's Prompt monad ( http://www.mail-archive.com/haskell-cafe@haskell.org/msg33040.html ) and wondered if it might be useful for debugging and program analysis purposes

[Haskell-cafe] Prompt Monad

2008-08-12 Thread Martin Hofmann
I just came across last year's thread about Ryan Ingram's Prompt monad ( http://www.mail-archive.com/haskell-cafe@haskell.org/msg33040.html ) and wondered if it might be useful for debugging and program analysis purposes. In particular, I thought about enforcing program decisions interactively.

[Haskell-cafe] syntactic anti-unification of TH terms --- best practise?

2008-07-18 Thread Martin Hofmann
I am implementing syntactic anti-unification for TH terms (Exp, Pat, Clause, ...). For example anti-unifying the clauses tail (1:xs) = xs tail (1:2:xs) = (2:xs) would yield tail (1:x1) = x1 whereas the anti-instance of last (1:[]) = 1 last (1:xs) =

Re: [Haskell-cafe] syntactic anti-unification of TH terms --- best practice?

2008-07-18 Thread Martin Hofmann
Don't you need to do this translation anyway, because Pat and Exp use different constructors? Yes, somewhere I have to say how to convert Pat to Exp. Perhaps you can reduce some of the lookup cases to looking up just Pat and Exp (eg, looking up in a Body or Clause or Pat or Exp could

[Haskell-cafe] Re: Re: Re: Reflective capabilities of Haskell (cont'd)

2008-03-13 Thread Martin Hofmann
On Wed, 2008-03-12 at 15:59 -0400, Jeff Polakow wrote: Data.Generics allows you to do this (to a certain extent), i.e. there is a function dataTypeConstrs :: DataType - [Constr] It might be hard, or even impossible, to get Data.Typeable and Data.Generics to play with each

[Haskell-cafe] Re: Re: Reflective capabilities of Haskell (cont'd)

2008-03-12 Thread Martin Hofmann
Data.Typeable gives you most of what you want except for access to function bodies. Thanks a lot, this helps a bit, but access to function bodies is exactly what I need. Or being more precise, I need the functionality of ghci's command ':t'. So functions that behave as follows, where

[Haskell-cafe] Reflective capabilities of Haskell

2008-03-11 Thread Martin Hofmann
I am trying to port a programme written in Maude, which is a reflective language based on rewriting logic ( http://maude.cs.uiuc.edu/ ), to Haskell. I thought using Template Haskell might be a good idea, but I got stuck and now I am wondering if this is really possible in Haskell. Let me give an

[Haskell-cafe] Reflective capabilities of Haskell (cont'd)

2008-03-11 Thread Martin Hofmann
I am trying to port a programme written in Maude, which is a reflective language based on rewriting logic ( http://maude.cs.uiuc.edu/ ), to Haskell. I thought using Template Haskell might be a good idea, but I got stuck and now I am wondering if this is really possible in Haskell. Let me give an

[Haskell-cafe] Mission: To take args from an n-tuple ... generally

2008-01-31 Thread Martin Hofmann
Dear Community. I have recently read Joel Koerwer's posting how to evaluate a function of type (a-a-...-a-a), taking the arguments from a list (http://haskell.org/pipermail/haskell-cafe/2006-October/018658.html). Therefore, he introduced a function multApply: multApply :: (a-a-...-a-a) -

Re: [Haskell-cafe] Mission: To take args from an n-tuple ... generally

2008-01-31 Thread Martin Hofmann
I wondered, why not take an n-tuple of arguments s.t. multApply' :: (a1-a2-...-an-o) - (a1,(a2,(...(an,o)...))) - o I'm not sure what you're trying to do here. Why is there an o in the argument? Also, do you really mean the number of arguments expected to match the number of