On Thu, 2007-04-19 at 09:31 +0200, Wolfgang Jeltsch wrote:
> > A much better solution would be to upgrade to David Waern's
> > expiremental fork of Haddock, which does parsing using the GHC API and
> > can handle all the syntactic constructs GHC can:
> >
> > http://darcs.haskell.org/SoC/haddock.gh
Am Donnerstag, 19. April 2007 00:20 schrieben Sie:
> On Wed, Apr 18, 2007 at 07:29:21PM +0200, Wolfgang Jeltsch wrote:
> > Hello everybody,
> >
> > I urgently need Haddock support for type operators like in the following
> > code snippet:
> >
> >
On Wed, Apr 18, 2007 at 07:29:21PM +0200, Wolfgang Jeltsch wrote:
> Hello everybody,
>
> I urgently need Haddock support for type operators like in the following code
> snippet:
>
> infix 2 :::, :=
> infixl 9 :.:
>
> data name ::: value = name := value
Am Mittwoch, 18. April 2007 19:29 schrieb Wolfgang Jeltsch:
> Hello everybody,
>
> I urgently need Haddock support for type operators like in the following
> code snippet:
>
> infix 2 :::, :=
> infixl 9 :.:
>
> data name ::: value = name := value
>
Hello everybody,
I urgently need Haddock support for type operators like in the following code
snippet:
infix 2 :::, :=
infixl 9 :.:
data name ::: value = name := value
newtype Composition f g a = Composition { runComposition :: f (g a) }
type (:.:) = Composition
Does
Pedro Vasconcelos wrote:
On Mon, 18 Oct 2004 09:51:52 +0200
"Georg Martius" <[EMAIL PROTECTED]> wrote:
On Mon, 18 Oct 2004 09:43:26 +0200, Peter Theissen <[EMAIL PROTECTED]> wrote:
Hi,
is there any possibility of defining Infix-/Postfixoperators
in Haskell?
Example:
Plus :: Int, Int -> Int
>>>Plus
Lest it all be explanation by example, the story basically goes like
this:
Binary functions can be used in infix style by surrounding the
function name by backticks (plus x y <=> x `plus` y)
Binary operators can be used in prefix style by enclosing it in
parentheses ( 4 + 3 <=> (+
On Mon, 18 Oct 2004 09:51:52 +0200
"Georg Martius" <[EMAIL PROTECTED]> wrote:
> Hi,
>
> On Mon, 18 Oct 2004 09:43:26 +0200, Peter Theissen <[EMAIL PROTECTED]> wrote:
>
> > Hi,
> > is there any possibility of defining Infix-/Postfixoperators
> > in Haskell?
> >
> > Example:
> > Plus :: Int, Int -
One easy way:
> plus :: Int -> Int -> Int
> plus x y = x + y
> times2 x = x `plus` x
--
Janis Voigtlaender
http://wwwtcs.inf.tu-dresden.de/~voigt/
mailto:[EMAIL PROTECTED]
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/
Hi,
On Mon, 18 Oct 2004 09:43:26 +0200, Peter Theissen <[EMAIL PROTECTED]> wrote:
Hi,
is there any possibility of defining Infix-/Postfixoperators
in Haskell?
Example:
Plus :: Int, Int -> Int
Plus :: Int -> Int -> Int
Plus x y = x + y
an now IÂm want to use Plus in another function as an infix:
Tim
Hi,
is there any possibility of defining Infix-/Postfixoperators
in Haskell?
Example:
Plus :: Int, Int -> Int
Plus x y = x + y
an now I´m want to use Plus in another function as an infix:
Times2:: x = x Plus x
Is this possible anyway?
If this feature doesnt exist, could you please
give some reasons
At 14:05 02/08/04 -0700, John Meacham wrote:
You might be interested in my BooleanAlgebra class, which replaces the
various boolean operators from the prelude with overloaded versions
with various useful instances.
The really nice thing is the instance for Bool is exactly the same as
the prelude
On Mon, Aug 02, 2004 at 10:54:33PM +0200, [EMAIL PROTECTED] wrote:
> The operators can be also defined as follows:
>(.&.) f g x = (f x) && (g x)
>(.|.) f g x = (f x) || (g x)
>
> It is clear from these definitions, that the operators are ternary
> op
ineTest :: (b->c->d) -> (a->b) -> (a->c) -> a -> d
combineTest c t1 t2 = \a -> c (t1 a) (t2 a)
(.&.) :: (a->Bool) -> (a->Bool) -> (a->Bool)
(.&.) = combineTest (&&)
(.|.) :: (a->Bool) -> (a->Bool) -> (a->Bool)
(.|.) = combine
Andrew J Bromage wrote:
As a matter of interest, is there a known worst-case complexity for
the precomputation required by Earley's algorithm to handle arbitrary
CFGs?
Earley's algorithm handles exactly arbitrary (in particular ambiguous)
CFGs without precomputation.
see i.e. Aho,Ullman, "The The
G'day all.
On Mon, Jul 21, 2003 at 01:07:39PM +0200, Christian Maeder wrote:
> >>Mere overload resolution (over monomorphic types) is not NP-hard. (This
> >>is only a common misconception.)
>
> I can only repeat my above sentence.
I'm a firm believer in the maxim that the best way to find info
.
Remember that the situation we're looking at is that there are a small
number of operators (e.g. those which work on number-like types) which
people want to heavily overload. A program which used a mixture of
these types could easily tickle exponential behaviour quite quickly if
the programm
G'day all.
On Sat, Jul 19, 2003 at 01:52:32AM -0400, Dylan Thurston wrote:
> It's maybe easiest to think in terms of group theory with an
> action on a set: you're just distinguishing between the multiplication
> of group elements and the actual action. This distinction is not
> usually reflecte
On Saturday, 2003-07-19, 07:52, CEST, Dylan Thurston wrote:
> [...]
> But if you have -Point, then you have a 0 Point, and there's no distinction
> between Points and Vectors at all!
Yes, I always thought (and still think) that the (main) difference between
points in affine geometry and radius v
On Sat, Jul 19, 2003 at 02:06:44PM +1000, Andrew J Bromage wrote:
> G'day all.
>
> On Fri, Jul 18, 2003 at 04:08:25AM -0400, Dylan Thurston wrote:
>
> > What's wrong with that solution?
>
> Working with these operators, I would spend a significant am
wise doing something dubious?"
Remember that the situation we're looking at is that there are a small
number of operators (e.g. those which work on number-like types) which
people want to heavily overload. A program which used a mixture of
these types could easily tickle exponenti
G'day all.
On Fri, Jul 18, 2003 at 04:08:25AM -0400, Dylan Thurston wrote:
> What's wrong with that solution?
Working with these operators, I would spend a significant amount of
time getting the '<' and '>' notations right rather than writing
code. I d
a b -> c, c a -> b, c b -> a where
(+) :: a -> b -> c
class (Additive c b a) => Subtractive a b c where
(-) :: a -> b -> c
> One solution might be to relax the rules about how the types of
> operators are resolved. At the moment, you can define function
> names
load resolution (over monomorphic types) is not NP-hard. (This
is only a common misconception.)
Operators with function profiles can be viewed as context free grammar
productions where the types are non-terminals. Overlaod resolution, like
for ADA, corresponds then to the word problem for contex
oint - Vector = Point
Vector - Point = Point -- (this rule is a bit controversial)
Point - Point = Vector
It's not obvious what to call the operators here.
One solution might be to relax the rules about how the types of
operators are resolved. At the moment, you can define funct
G'day all.
On Thu, Jul 17, 2003 at 05:21:47PM +0200, Christian Maeder wrote:
> Why do you outrule other useful libraries (see above). In fact ($) is
> quite cryptic (for a non-Haskeller).
Actually this gives me a perfect opportunity to rant a bit. :-)
($) is a wart, even for a Haskeller. It h
Wolfgang writes:
> I think, in both cases you don't define an *operator*. LaTeX probably won't
> use the correct spacing around the symbol.
>
> A related problem is that I cannot see a way to define a new "log-like
> function" (as Lamport names them), i.e., a function with a name consisting of
Wolfgang Jeltsch wrote:
On Thursday, 2003-07-17, 09:08, CEST, Johannes Waldmann wrote:
A similar discussion sometimes surfaces in mathematics - where they have
"user-defined" operators all over the place, and especially so since LaTeX.
Well, for the most part, LaTeX only provi
> Well, for the most part, LaTeX only provides common operators. One problem, I
> came across some weeks ago, is that it is *not* possible to define his/her own
> operators (or, at least, that Lamport's "LaTeX - A Document Preparation
> System" doesn't tell you
gt; Indeed this is cute - but let me add a general comment here:
> in my code, I don't define any operators at all (only functions).
> I do think that self-defined operators make a programm less readable.
While I agree with that, I think that the language needs
"user"-defined ope
Johannes Waldmann wrote:
I do think that self-defined operators make a programm less readable.
I quite like most combinators from the pretty-printer or parsing libraries!
And what's absolutely horrible (IMHO) is to allow the user
to declare arbitrary precedence and associativity fo
are log, min, max, sin, cos and tan.
Check out the AMS-LaTeX package. I think it has a macro to solve this.
It also includes a zillion new symbols/operators.
http://www.ams.org/tex/amslatex.html
If you have TeTeX installed as your TeX system, then it should be
included.
--
Matthew Don
On Thursday, 2003-07-17, 16:07, CEST, Robert Ennals wrote:
> > Well, for the most part, LaTeX only provides common operators. One
> > problem, I came across some weeks ago, is that it is *not* possible to
> > define his/her own operators (or, at least, that Lamport's
On Thursday, 2003-07-17, 09:08, CEST, Johannes Waldmann wrote:
> [...]
> in my code, I don't define any operators at all (only functions). I do think
> that self-defined operators make a programm less readable. All you get is a
> A short cryptic sequence of non-alphanumeric cha
On Wed, 16 Jul 2003, K. Fritz Ruehr wrote:
> I think the cutest way to get what you want here is to define a new
^^
> operator as follows:
>
> (.<) = (.) . (.)
Indeed this is cute - but let me add a general comment here:
in my code, I don't define
On Monday, 2003-07-07, 09:46, CEST, Arun Kumar S Jadhav wrote:
> Hi All,
> How to define a new unary operator.
The only unary operator in Haskell is unary minus for negating numbers. There
are no other predefined unary operators and it is not possible to define any.
So unary mi
Hi All,
How to define a new unary operator.
E.g:
I want to use "/\" for intersection over a list of sets
and similarly "\/" for union over a list of sets.
I searched haskell98 report but couldn't find any pointers. Please
let me know if it's allowed in the first place, i
Wed, 26 Apr 2000 23:49:43 -0700, Mike Jones <[EMAIL PROTECTED]> pisze:
> (||*):: Vi Bool -> Vi Bool -> Vi Bool
> b1 ||* b2 = do
> p <- b1
> if p then return True else b2
The definition does not use anything specific to this particular monad.
The most general type that
I am trying to invent an embeeded language for measurement instruments. To
do this, I modeled an instrument after the robot language in The Haskell
School of Expression.
For my instrument:
newtype Vi a = Vi (ViState -> (ViState, a))
I have defined:
(||*) :: Vi Bool -> Vi Bool -> Vi Bool
b1 ||*
Libor Skarvada wrote:
>
> David Feuer writes:
> > I really don't like the fact that the unary "-" is special in Haskell.
> > I propose that along with infix operators, Haskell support prefix and
> > postfix operators. The negative function could be re
I really don't like the fact that the unary "-" is special in Haskell.
I propose that along with infix operators, Haskell support prefix and
postfix operators. The negative function could be renamed to, randomly,
%-.
I also suggest that the operators be divided into categories,
le) proposals, this would need to be the
> | symbol (:+:) -- or characters to that effect -- for consistency.
>
>I agree.
>
>Note that the symbol (+) as a type, would become a type _variable_. I
>think, just as it is usefule to have (+) as a formal parameter of a
>function, it is
be the
| symbol (:+:) -- or characters to that effect -- for consistency.
I agree.
Note that the symbol (+) as a type, would become a type _variable_. I
think, just as it is usefule to have (+) as a formal parameter of a
function, it is useful to have operators as type variables also.
See the f
Original-Via: uk.ac.nsf; Wed, 29 Jan 92 15:14:28 GMT
John Peterson writes:
I was planning to stand aside on syntax issues, but this is going too far!
Simon proposes:
the back-quote stuff in the lexical syntax,
and the paren-ifying in the ordinary syntax.
[..
Original-Via: uk.ac.nsf; Fri, 24 Jan 92 00:07:18 GMT
Original-Sender: [EMAIL PROTECTED]
If I wasn't such a wimp at this point I would have argued as John has;
his argument was exactly why Joe and I made the change. However, the
reality is that I have become a wimp (about syntax, anyway). Perhap
Original-Via: uk.ac.nsf; Thu, 23 Jan 92 22:28:37 GMT
> So I propose:
> the back-quote stuff in the lexical syntax,
> and the paren-ifying in the ordinary syntax.
> Does anyone else have an opinion. I don't think there are any technical
> issues here; just stylistic.
Original-Via: uk.ac.nsf; Thu, 23 Jan 92 21:22:37 GMT
Original-Sender: [EMAIL PROTECTED]
I was planning to stand aside on syntax issues, but this is going too far!
Simon proposes:
the back-quote stuff in the lexical syntax,
and the paren-ifying in the ordinary syntax.
Kevin adds:
Original-Via: uk.ac.nsf; Sat, 18 Jan 92 14:50:25 GMT
Backquotes with or without whitespace are both fine with me. Paul and I
did in fact discuss this, and when he made his decision, I think it was
a pretty close call.
--Joe
|I see from Joe's revised syntax that he proposes allowing
|
|
allow to write lists like
[+,*,-]
but at most places one had still to put parentheses around the
operators. In any case, white-space around the operators would be
allowed, of course.
Similarly one could move the sections to the corresponding
exp^i, e.g. a further alternative for exp^i wou
> So I propose:
> the back-quote stuff in the lexical syntax,
> and the paren-ifying in the ordinary syntax.
>
> Does anyone else have an opinion. I don't think there are any technical
> issues here; just stylistic.
>
> Simon
I agree with you, Simon. Errors from unmatched backquo
I see from Joe's revised syntax that he proposes allowing
( {-white space-} + {-white space-} )
where previously only (+) was allowed. That seems great to me.
He also proposed allowing
` {-white space-} f {-white space-} `
where previously only `f` was allowed. I can see th
Original-Via: uk.ac.st-and.cs; Sat, 28 Sep 91 14:29:42 BST
A minor point.
Since '<-' is not an operator should it be a reservedop (presumably the
reserved operators are a subset of the operators)? I suggest that '<-'
(but not '->') should be a special.
Tony
52 matches
Mail list logo