[Haskell-cafe] getting a DB library working with ghc 6.6 and PostgreSQL 7.4.7
I'm looking for an alternative to HSQL for database connectivity -- the lack of prepared statements in HSQL is particularly worrisome. I installed HDBC, but when I tried running a simple program that used it, I get the error message ghc-6.6: /usr/local/lib/HDBC-postgresql-1.0.1.0/ghc-6.6/HSHDBC-postgresql-1.0.1.0.o: unknown symbol `PQserverVersion' Looking more closely at the README.txt file there, it seems that the PostgreSQL driver is expecting 8.1, and I'm using 7.4.7. I installed the ODBC driver, and I know that in theory one can connect to my PostgreSQL server with ODBC, but as far as I can tell from the documentation, I would have to configure a separate DSN for every database instance that I would want to connect to, which makes it kind of useless for a utility that any user could pass database names to on the command line. The takusen package looks interesting, but when I checked it out and tried to build it (with "ghc --make -o setup Setup.hs"), I got the error message Setup.hs:6:7: Could not find module `Distribution.Compat.FilePath': it is hidden (in package Cabal-1.1.6) How do I work around these? Is there another library worth looking into? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Automatic fixity allocation for symbolic operators
I would imagine (reading into Jon Fairbairn's note) that the difficulty is in combining it with the traditional handling of precedences in parsing systems, as Bulat was describing. AFAIK, which is not much on this topic, the notion of precedence in traditional LR spewers is strictly tied to numeric precedences that are known pretty much a priori. Since mapping all the way to numbers seems like overkill to resolve such infix ambiguities, I'd expect such an adjustment to parser generators wouldn't be horrific--it may even be more natural on the implementation side. Nick On 10/16/06, Arie Peterson <[EMAIL PROTECTED]> wrote: Good evening, Bulat Ziganshin wrote: > but when you want to have user-defined operators, that will mean that > you need either to define precedences to all other operators > (including those from other libs), or sometimes user programs will not > compile because they used combination of operators with undefined > precedence > > good for making good headache :) Why is that? A library would indeed only declare the relative precedence of its operators with respect to operators that 1) it knows of; and 2) are related (or general) enough so that there is a reasonable choice of precedence. I think it is even good to force the user to declare any other, more uncommon, precedences; better than the current situation, where the relative precedence of operators from unrelated libraries is fixed pretty much arbitrarily, as an artefact of the imposed total order. Regards, Arie -- Mr. Pelican Shit may be Willy. ^ /e\ --- ___ 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] Error detection in GLR Happy grammar
P.C.Callaghan wrote: > Hello, > > "error" isn't implemented yet in GLR mode - it is ignored. > > Note that yacc-style error handling can't be transplanted directly into > GLR, since the nature of parse errors is not the same. In LR(k) errors > mean that the single parse can't continue and hence some remedial action > is needed. In GLR, it could mean this (when following one unique parse), > or with multiple parses that some are being dropped because further input > has ruled them out. Recovery on the latter probably isn't correct - they > should be discarded. > As far as I understand, if you don't do any IO actions, like printing error messages as soon as an "error" found (which could not be so, since the GLR parsing will end OK if at least a complete parsing tree is found) a proper result could be returned and everything should go fine. > I might try allowing an explicit error token which acts only when one > parse is live, and follow standard Happy behaviour for this. If you have > an example to test on, it might be useful. > I have a big grammar that might be great for this. However, I haven't specified the error recovery points in the productions yet, since I couldn't generate an LR parser with no conflicts. In fact, I tried solving these conflicts, but I found that the information Happy gives me about them is not informative enough: I couldn't even understand why some conflicts took place at specific positions. > Note that for failed parses, you are given a list of unconsumed tokens and > the partial parses constructed so far, so some diagnosis is possible. > At this moment, our parser prints an error in the form of "line:column:error: Unexpected token 'TokenType'". The main problem here is that I don't want my compiler to stop as soon as a parsing error is found, but to recover from it and report all the errors at the end. I tried encapsulating the real return status of the parsing in a monad, so I can later know if the parsing was really OK or the ParseOK result I'm given is the result of recovering from an error. Then I realized I couldn't detect parsing errors like in LR and stopped doing this : ( > > Paul > > > ps. I've almost fixed the module header problem you mentioned before. > > ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: Automatic fixity allocation for symbolic operators
Good evening, Bulat Ziganshin wrote: > but when you want to have user-defined operators, that will mean that > you need either to define precedences to all other operators > (including those from other libs), or sometimes user programs will not > compile because they used combination of operators with undefined > precedence > > good for making good headache :) Why is that? A library would indeed only declare the relative precedence of its operators with respect to operators that 1) it knows of; and 2) are related (or general) enough so that there is a reasonable choice of precedence. I think it is even good to force the user to declare any other, more uncommon, precedences; better than the current situation, where the relative precedence of operators from unrelated libraries is fixed pretty much arbitrarily, as an artefact of the imposed total order. Regards, Arie -- Mr. Pelican Shit may be Willy. ^ /e\ --- ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re[3]: [Haskell-cafe] Automatic fixity allocation for symbolic operators
Hello Nicolas, Monday, October 16, 2006, 6:31:42 PM, you wrote: > What if operator precedences were specified as a partial order instead > of using numbers? > precInherit <*> -> @*@ > precAll ?+? > ?*? > Regarding precAll: I'm not a regular expressions/glob for semantics > fan, but you get the idea. > The idea is to define a partial order on operators and let undecided > operator relationships remain undefined. Composition remains an open > issue, but perhaps someone else will have a light bulb about that. well, it is what typically done when you define expression parsers by hand (for any language that had fixed precedences). smth like this: expr1 ::= expr2 | expr1 + expr2 | expr1 - expr2 expr2 ::= expr3 | expr2 * expr3 | expr2 / expr3 expr3 ::= ... but when you want to have user-defined operators, that will mean that you need either to define precedences to all other operators (including those from other libs), or sometimes user programs will not compile because they used combination of operators with undefined precedence good for making good headache :) -- Best regards, Bulatmailto:[EMAIL PROTECTED] ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: Automatic fixity allocation for symbolic operators
"Nicolas Frisby" <[EMAIL PROTECTED]> writes: > What if operator precedences were specified as a partial order instead > of using numbers? I suggested something that did that to fplangc back in 1987... Thu, 19 Nov 87 17:49:50 GMT in fact! Simon PJ later forwarded a message from Stef Joosten to similar effect... I made a more concrete proposal later and Phil Wadler tidied it up. I think It even got as far as a draft of the language, but I think it was decided that it was just too difficult (both for human and computer) to parse. -- Jón Fairbairn [EMAIL PROTECTED] http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html (updated 2006-09-13) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: Automatic fixity allocation for symbolic operators
Nicolas Frisby wrote: > What if operator precedences were specified as a partial order instead > of using numbers? Henning Thielemann wrote: > dict.leo.org says: "great minds think alike" Funny, I thought of this too. It seems very natural. You would probably want an implicit taking of transitive closure, to reduce the needed number of declarations. However, to consistently parse an expression, the precedence relation does not need to be transitive (right? one only needs to compare the precedence of adjacent operators), so you could even allow cycles in the precedence graph :s - not sure if that would ever be useful. > Perhaps Brian's original idea of systematically determining > unspecified operator precedences could be recast in this system. > Consider (woefully under contemplated) precedence specifiers such as: > > precInherit <*> -> @*@ > precAll ?+? > ?*? > > Regarding precAll: I'm not a regular expressions/glob for semantics > fan, but you get the idea. I'm not convinced that it would be helpful to attach some special meaning to the "layout" of the operator symbol. -- Mr. Pelican Shit may be Willy. ^ /e\ --- ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Automatic fixity allocation for symbolic operators
On Mon, 16 Oct 2006, Nicolas Frisby wrote: > Regarding latticess and locality... > > This idea probably won't help with editors, but the OP's question has > sparked a discussion here and some thinking in my head--thanks Brian. > > What if operator precedences were specified as a partial order instead > of using numbers? Using numbers implies a potentially deceptive sense > of completeness: "well I've given @+@ a precedence 5 and let that be > written in stone forever so that all conflicts are resolved > henceforth." > > Most fixities I've dealt with are put into play only amongst related > operators in a project (@+@ or @*@ in MySpecialLib) or amongst > operators from a related library. If the syntax were like: > > infixr @+@ > infixr @+@ > prec @+@ > @*@ dict.leo.org says: "great minds think alike" http://www.haskell.org/pipermail/haskell-cafe/2005-February/009260.html ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: Re: [Haskell-cafe] Automatic fixity allocation for symbolic operators
Regarding latticess and locality... This idea probably won't help with editors, but the OP's question has sparked a discussion here and some thinking in my head--thanks Brian. What if operator precedences were specified as a partial order instead of using numbers? Using numbers implies a potentially deceptive sense of completeness: "well I've given @+@ a precedence 5 and let that be written in stone forever so that all conflicts are resolved henceforth." Most fixities I've dealt with are put into play only amongst related operators in a project (@+@ or @*@ in MySpecialLib) or amongst operators from a related library. If the syntax were like: infixr @+@ infixr @+@ prec @+@ > @*@ then the programmer gets to specify as much as they have decided and no more. 5 @+@ 3 * 7 would simply be under defined and would require parens. Perhaps Brian's original idea of systematically determining unspecified operator precedences could be recast in this system. Consider (woefully under contemplated) precedence specifiers such as: precInherit <*> -> @*@ precAll ?+? > ?*? Regarding precAll: I'm not a regular expressions/glob for semantics fan, but you get the idea. The idea is to define a partial order on operators and let undecided operator relationships remain undefined. Composition remains an open issue, but perhaps someone else will have a light bulb about that. Nick On 10/16/06, Arie Peterson <[EMAIL PROTECTED]> wrote: Hello, Henning Thielemann wrote: > [...] I repeat my example of a source code formatting tool which must > decide whether to format > > a + >b * c > > or > > a + b * >c > > It needs to know the precedences of the used operators, which, as Brian > pointed out, is possibly not even defined somewhere. Alternatively > consider a compiler which must have a parser that must adapt the grammar > to the module contents (infix statements) in order to parse the module > correctly. Even worse: The same symbol can have different precedences, > because infix operators can be declared locally. I would suggest to first parse modulo fixity and precedence (keep all operator applications in flat lists) and only later, if/when precedence and fixity information is available, parse those operator lists. > The same problem for a > human: In order to analyse the meaning of an expression with infix > operators he must know the precedences. That is, problems with infix > operators are by far not bound to a text editor! Quite so. I wouldn't consider it a problem though. The meaning of the expression also depends on the meaning (definition) of the operators involved, and of other functions used in the expression. That information may also be located elsewhere or even not yet available, just as precedence declarations. Locality has been wittingly sacrificed for flexibility. Regards, Arie -- Mr. Pelican Shit may be Willy. ^ /e\ --- ___ 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] Automatic fixity allocation for symbolic operators
Hello, Henning Thielemann wrote: > [...] I repeat my example of a source code formatting tool which must > decide whether to format > > a + >b * c > > or > > a + b * >c > > It needs to know the precedences of the used operators, which, as Brian > pointed out, is possibly not even defined somewhere. Alternatively > consider a compiler which must have a parser that must adapt the grammar > to the module contents (infix statements) in order to parse the module > correctly. Even worse: The same symbol can have different precedences, > because infix operators can be declared locally. I would suggest to first parse modulo fixity and precedence (keep all operator applications in flat lists) and only later, if/when precedence and fixity information is available, parse those operator lists. > The same problem for a > human: In order to analyse the meaning of an expression with infix > operators he must know the precedences. That is, problems with infix > operators are by far not bound to a text editor! Quite so. I wouldn't consider it a problem though. The meaning of the expression also depends on the meaning (definition) of the operators involved, and of other functions used in the expression. That information may also be located elsewhere or even not yet available, just as precedence declarations. Locality has been wittingly sacrificed for flexibility. Regards, Arie -- Mr. Pelican Shit may be Willy. ^ /e\ --- ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Extended functionality for record field accessors
Here is some proposal for Haskell 2 1/2 or so: {- | In Haskell 98 the name of a record field is automatically also the name of a function which gets the value of the according field. E.g. if we have @ data Pair a b = Pair {first :: a, second :: b} @ then @ first :: Pair a b -> a second :: Pair a b -> b @ However for setting or modifying a field value we need to use some syntactic sugar, which is often clumsy. @ modifyFirst :: (a -> a) -> (Pair a b -> Pair a b) modifyFirst f r@(Pair {first=a}) = r{first = f a} @ We propose to extend the meaning of the record field names to a function which allows setting, getting and modifying values easily. -} module RecordAccess where import Control.Monad.State (MonadState) import qualified Control.Monad.State as State {- | The access functions we propose, look very similar to those needed for List.mapAccumL (but parameter order is swapped) and State monad. They get the new value of the field and the record and return the old value of the field and the record with the updated field. -} type Accessor r a = a -> r -> (a, r) {- * Access helper functions, these are similar to State methods and should be in Prelude -} {- | Set the value of a field. -} set :: Accessor r a -> a -> r -> r set f x = snd . f x {- | Get the value of a field. -} get :: Accessor r a -> r -> a get f = fst . f undefined {- | Transform the value of a field by a function. -} modify :: Accessor r a -> (a -> a) -> (r -> r) modify f g rOld = let (a,rNew) = f (g a) rOld in rNew {- * Access helper functions in a State monad. -} setState :: MonadState r m => Accessor r a -> a -> m () setState f x = State.modify (set f x) getState :: MonadState r m => Accessor r a -> m a getState f = State.gets (get f) modifyState :: MonadState r m => Accessor r a -> (a -> a) -> m () modifyState f g = State.modify (modify f g) {- * Example accessors for the pair type -} {- | Access to the first value of a pair. -} first :: Accessor (a,b) a first xNew (xOld,y) = (xOld, (xNew,y)) {- | Access to the second value of a pair. -} second :: Accessor (a,b) b second yNew (x,yOld) = (yOld, (x,yNew)) {- * Example accessors for the pair type -} {- | Example of using 'set', 'get', 'modify'. -} example :: Int example = get second $ modify second succ $ set first 'a' $ ('b',7) exampleState :: State.State (Char,Int) Int exampleState = do setState first 'a' modifyState second succ getState second ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Automatic fixity allocation for symbolic operators
On Sat, 14 Oct 2006, Jim Apple wrote: > On 10/14/06, Brian Hulley <[EMAIL PROTECTED]> wrote: > > User defined fixities are an enormous problem for > > an interactive editor > > This is the second or third time you've proposed a language change > based on the editor you're writing. I don't think this is a fruitful > avenue. I assume that editor developers, compiler writers and language tool writers (documentation extraction, source code formatting) get much more insight into syntactic issues than other users. Finding some problem when implementing one of these tools often reveals weak points in the language syntax. I repeat my example of a source code formatting tool which must decide whether to format a + b * c or a + b * c It needs to know the precedences of the used operators, which, as Brian pointed out, is possibly not even defined somewhere. Alternatively consider a compiler which must have a parser that must adapt the grammar to the module contents (infix statements) in order to parse the module correctly. Even worse: The same symbol can have different precedences, because infix operators can be declared locally. The same problem for a human: In order to analyse the meaning of an expression with infix operators he must know the precedences. That is, problems with infix operators are by far not bound to a text editor! You may argue that difficult language syntaxes like that of C++ push the parser technique forward. However this seems to me like Windows pushes memory development. Concerning the automatic precedence assigment according to the characters in an infix operator, I think that it is difficult to find a reasonable algorithm, because that algorithm would also limit the kind of operator schemes that can be used. If the operations can be associated with basic mathematical operations like +, *, =, then it would work, but what about different structures? How would you translate lattice operations "up" and "down", how operations like "parallel" and "serial" composition? Summed up, I think infix handling must be somehow improved, but I don't know how. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Debugging Newton's method for square roots
Clifford Beshers <[EMAIL PROTECTED]> writes: > There was some excellent advice in the other responses, but I thought > it worth mentioning that your Haskell code converges if you step up > from Float -> Float to Double -> Double. Used to be faster, too, IIRC. Is that still the case? -k -- If I haven't seen further, it is by standing in the footprints of giants ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe