Re: [Haskell] Mixing monadic and non-monadic functions

2004-03-23 Thread ozone
On 24/03/2004, at 9:54 AM, Sean E. Russell wrote:

We'd all love to make the lifting implicit, but no one knows how to 
do it
without breaking the whole language.
I've heard people talk about the functional purity of Haskell -- 
you'd have
to break this purity to add implicit lifting?
I don't think you would break the functional purity of Haskell if you 
did such a thing, but you'd probably need some new syntax to help out 
the type system.  Perhaps something like:

assertBool fail $ length (somefunc a) == length (somefunc b)

So here, (a) performs the same function as the - operator, but 
assigns the result to an anonymous variable and is instantly consumed 
by whatever function uses its value.  Please don't berate me for my 
choice of syntax, by the way: that was just an example :).

One problem with this is that you now don't know what order those two 
operations take place: does somefunc a run first, or does somefunc 
b run first?  You have this same problem in other imperative languages 
too; I'm not sure if, e.g. C defines an order for function evaluation 
to occur.  Perhaps you could just dictate a left-to-right order, or 
maybe come up with bizarre (1 ... ) and (2 ... ) constructs to 
indicate what order things should run in.  Some ideas to get started, 
anyway.

I do agree with you that not having syntactic sugar to do something 
like that is somewhat inconvenient, and it would be a nice addition to 
the language.

A related problem which was discussed here recently is Haskell's lack 
of
per-type namespaces, something which even C programmers take for 
granted.
Again, the problem is the tricky interaction with type inference.
Augh!  Yes!  I've hit that as well.  Well, in my case, it was 
constructors.  I
was trying to do:

data Effort = Easy | Middle | Hard
data Impact = Low | Middle | High
Perhaps one option for this would be to have explicitly quantified data 
namespaces, so that you would have to write 'Effort.Middle' to 
construct something of type Effort, and 'Impact.Middle' to construct 
something of type Impact.

The problems you mention of in Haskell are certainly solvable: it's 
just the mere matter of implementing such features ... :)  I think the 
Haskell community (at least, the community who are capable of making 
such changes to the Haskell implementations) is unfortunately a bit too 
small to put such syntactic niceties in the language; we simply don't 
have enough human resources to do it.  But I'm sure plenty of others 
would agree that those features would be nice!

--
% Andre Pang : trust.in.love.to.save
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-27 Thread ozone
On 27/02/2004, at 9:51 AM, David Bergman wrote:

So at the moment, many Haskellers will append the type name to the
function to indicate that it only works on that particular data type.
In this respect, Haskell is at a disadvantage vs most object-oriented
languages, because in them, you can write x.add, and the type system
will perform object-oriented polymorphism for you and call the
correct add method, no matter if x is a FiniteMap or a Set.  Writing
addToFM fm ... or addToSet set ... is surely a lot more
inconvenient than writing fm.add or set.add, no?
Yes. But, you are refering to overloading, no? And, not subtype 
polymorphism
(which is what I denote with object-oriented polymorphism)? Just to 
make
things clear in my mind.
Yes, what I'm referring to is essentially overloading.  I called it 
object-oriented polymorphism because that's typically what OO people 
call such a thing :).  (I should know better to use OO terminology on a 
Haskell list; won't happen again ...).  However, it's form of 
overloading that Haskell cannot currently handle  well with type 
classes -- Oleg's post proves that you can do it, of course, but that's 
a (very good) hack rather than a long-term solution.

So, you have thought of automatically, but implicitly, introduce a 
namespace
for each data type, and then have Haskell employ Koenig Lookup, to 
decide
which function an expression is refering to?
It's a bit like Koenig lookup in that it has the same effect, although 
it's probably easier for the compiler to infer the namespace wanted, 
since we write expr.function ... rather than function expression 
  Writing function expression ... would work too, but then it 
looks like a standard function call rather than a function call 
associated with a particular type, and I think that causes more 
confusion.  Long-time Haskell users understand that writing foo.f 
means use f in namespace foo; changing around the language semantics 
to mean that f foo now means use f in namespace foo would make lots 
of people rather unhappy :).

You realize, of course, that mere intranamespacial parameter type 
lookup
(regular overloading) would achieve the same effect, without the 
(implicit)
namespaces?
I'm not sure what you mean by intranamespcial parameter type lookup 
-- can you explain?

There are a number of means by which the x in x.add can be
communicated to the actual function: it's similar to the hidden 'self'
or 'this'
variable that's present when you invoke a method on an object in OO.
Perhaps x is passed to the function as its first parameter, or maybe
it could be its last parameter, or even an arbitrary parameter (where
the parameter it's passed as could be defined in the type signature of
the function).  Perhaps 'self' or 'this' could be an implicit
parameter.
Any one of them will work just fine, I think.
Again, I think you are confusing the runtime dispatching subtype 
polymorpism
from overloading. Overloading would do what you want, while the subtype
polymorphism could (still) be handled by class, and instances of 
classes,
the Generic Programming way.
I (think I) understand the difference between dynamic binding vs 
overloading: here, all I'm after is trying to use the type system to 
give us a very simple form of overloading (e.g. based on the first 
argument to a function), that gives us the same effect as a per-type 
name space.

--
% Andre Pang : trust.in.love.to.save
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-27 Thread ozone
On 27/02/2004, at 4:48 PM, Brandon Michael Moore wrote:

On Fri, 27 Feb 2004 [EMAIL PROTECTED] wrote:

On 27/02/2004, at 1:13 PM, [EMAIL PROTECTED] wrote:

1) now I have to manually declare a class definition for every single
function, and I have to declare it in advance before any module 
defines
that function (most serious problem; see below),

2) I then have to declare instances of that type class for every
function I define,
3) the type signature for phase reveals no clues about how to use that
function.
Declaring a type class instance is really no problem.
I agree that declaring a type class instance per function is not a huge 
deal (if it can be automatically done by the compiler).  However, 
declaring the instance first requires declaring the type class itself, 
and that _is_ a problem, because that's exactly what I'm trying to work 
around.  Without 20/20 hindsight, you cannot say with certainty what 
type signatures a generic function (like 'phase' or even 'add') can 
support, because it's not a generic function, it's a function which is

When you declare a type class, you are making a trade-off: you are 
saying that the interface for this function is forever set in stone, 
and it cannot be changed by any instances under any circumstances.  In 
return for saying that interface is immutable, you get two major 
benefits: (1) an immutable interface, i.e. so you can guarantee that 
whenever you use ==, you _know_ the type signature is :: Eq a = a - a 
- Bool, and no instance can try to subvert that (unless your name is 
Oleg ;), and (2) you get very powerful overloading capabilities.

However, the disadvantage of this tradeoff is that because the type 
signature is now set, you just used up another function name in the 
namespace.  So type classes are the wrong approach to solve this 
problem, because what I'm after is being able to clutter up a namespace 
as much as I like with whatever names I like, but I don't want a 
polymorphic function--I want a function which only operates on one 
specific, primary data type.

With the per-type namespace separation I'm advocating, you do not need
to know and declare in advance that each function will be 
overloaded,
you simply write a FiniteMap.add function and a Set.add function, and
you get a simpler form of namespace separation (or overloading) based
on the first parameter that's passed to it.  It is a solution which is
more _flexible_ than requiring type class definitions, and it is 
better
than having hungarian notation for functions.  In fact, I think that,
right now, if we replaced the current namespace separation offered by
the hierarchical module system, and instead only had this sort of
per-type namespace separation, things would still be better!
How much of the structure of the first paramater would you look at? 
Could
you an implementation for pairs that depended on the actual types in 
the
pair? I think you should try to take advantage of the existing type 
class
machinery as much as possible here, even if what you want are not 
exactly
(standard) type classes.
The idea is if you write fm.add, you look at the type of fm as much 
as possible.  If you see that fm is polymorphic, all bets are off, and 
the compiler raises an error and quits with prejudice.  If fm is 
monomorphic, you should be able to infer its type (which includes 
pairs/tuples) and thus know which namespace to select to find the 
correct add function.   So the main requirement for this to work is 
whether it's possible to infer the type of fm; since I'm not a type 
theorist, I have no idea if that is in fact possible at all.

I realise my idea isn't very general in that it only allows this
namespace lookup/overloading based on the type of a single argument
parameter, and I think it would be possible with a bit more thinking 
to
generalise it to work based on multiple arguments (e.g. via
argument-dependent lookup, or whatnot).  But even in its current form,
I honestly think it offers far more flexibility and would lead to
cleaner APIs than is currently possible.
Read the paper and see if you think something like that might be 
useful.
In any case, I think there's a decent chance that something useful for
this would also be useful for building interfaces to object-oriented
libraries, and vicea versa. I think there's probably something that 
covers
both cases nicely and uniformly.
I've had a read of both the SPJ/Shields paper on OO-style overloading 
in Haskell, and I've also had a skim over another paper called A 
Second Look at Overloading which describes another overloading 
calculus called System O.  I don't think either paper directly 
addresses the problem I'm trying to solve, although some elements in 
the paper (e.g. closed classes) may provide a framework which is 
capable of addressing the problem, if something like fm.add can be 
translated to such a framework via major syntactic sugar :).

--
% Andre Pang : trust.in.love.to.save

[Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-26 Thread ozone
I've had an idea stewing in my head to do with per-type function 
namespaces, that the current module namespace discussion reminded me 
about.  The problem is that there is a limited namespace for functions, 
so that if you define a new data type, it is unwise to call functions 
which work on that data type a very generic name such as 'add'.  An 
example of this is Data.FiniteMap and Data.Set: both data types define 
a function to add things to their respective data types.

addToFM :: Ord key = FiniteMap key elt - key - elt - FiniteMap key 
elt
addToSet :: Ord a = Set a - a - Set a

So at the moment, many Haskellers will append the type name to the 
function to indicate that it only works on that particular data type.  
In this respect, Haskell is at a disadvantage vs most object-oriented 
languages, because in them, you can write x.add, and the type system 
will perform object-oriented polymorphism for you and call the 
correct add method, no matter if x is a FiniteMap or a Set.  Writing 
addToFM fm ... or addToSet set ... is surely a lot more 
inconvenient than writing fm.add or set.add, no?

The idea that I've been throwing around is to be able to define a 
separate namespace for each type; a function can either belong in a 
global (default) namespace, or belong in a particular type's 
namespace.  So, in the above example, instead of writing addToFM fm 
..., we could instead associate an 'add' function with the FiniteMap 
type, so we could write fm.add ... instead.  Provided that fm's type 
is monomorphic, it should be possible to call the 'correct' add 
function; if we defined another 'add' function that's associated with 
the Set type, that will only get called if the 'x' in x.add is of 
type :: Set.  So, like OO languages which inherently give separate 
namespaces to their different objects, here we give separate namespaces 
to different (monomorphic) types.  In this case, if one simply writes 
add instead of x.add, the compiler throws an error, because there 
is no 'add' function defined in the default namespace; add is only 
defined when a programmer writes x.add where x :: FiniteMap or x :: 
Set[1].

There are a number of means by which the x in x.add can be communicated 
to the actual function: it's similar to the hidden 'self' or 'this' 
variable that's present when you invoke a method on an object in OO.  
Perhaps x is passed to the function as its first parameter, or maybe it 
could be its last parameter, or even an arbitrary parameter (where the 
parameter it's passed as could be defined in the type signature of the 
function).  Perhaps 'self' or 'this' could be an implicit parameter.  
Any one of them will work just fine, I think.

However, this scheme is only for functions which have such a 'primary' 
data type to be associated with, such as FiniteMap or Set.  For 
functions which are truly polymorphic (such as ==), you still leave 
them in the default namespace.  Perhaps it's sensible to even make it a 
requirement that functions in the default namespace must be 
polymorphic: if they are monomorphic, they are associated with 
operating on a specific data type, so they should belong in a 
type-specific namespace.  You then still guarantee that such 
commonly-used polymorphic functions cannot be 'hijacked' to have stupid 
type signatures; i.e. == is always guaranteed to be :: Eq a - a - 
Bool.

Anyhow, feedback is more than welcome; I would certainly welcome this 
addition if it's feasible.  It feels inferior to be typing in 'addToFM 
foo' all the time when our OO brethren type the simpler and more 
succinct 'foo.add', especially given that Haskell's type system is far 
more powerful!

1. I haven't thought hard enough about whether it would be possible to 
have the same function name in both the 'default' namespace as well as 
in per-type namespaces, but my gut feeling says it should be OK.

--
% Andre Pang : trust.in.love.to.save
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-26 Thread ozone
On 27/02/2004, at 3:47 AM, Keith Wansbrough wrote:

I've had an idea stewing in my head to do with per-type function
namespaces, that the current module namespace discussion reminded me
about.  The problem is that there is a limited namespace for 
functions,
so that if you define a new data type, it is unwise to call functions
which work on that data type a very generic name such as 'add'.
[..]
The idea that I've been throwing around is to be able to define a
separate namespace for each type; a function can either belong in a
global (default) namespace, or belong in a particular type's
namespace.
This feature would seem to be in competition with type classes; could
you elaborate on the relative advantages and disadvantages?  The type
class story has the advantage of being well understood and quite
effective, but there are certainly some limitations too.
I don't think type classes can solve the problem I'm trying to tackle.  
As an example of why, check out the types of FiniteMap and Set's 'add' 
functions:

addToFM :: Ord key = FiniteMap key elt - key - elt - FiniteMap key 
elt
addToSet :: Ord a = Set a - a - Set a

Note that the type of addToFM takes in two parameters (besides the 
FiniteMap itself): a key and an element, whereas the type of addToSet 
only takes in one parameter, which is the thing to add.  So, how can 
you come up with a type class which provides a polymorphic 'add' 
function, considering you don't even know how many parameters each data 
type's individual add function uses?

Even if you could define such a type class (which I don't think is 
possible), you then have one less function in the namespace to use, 
which is another problem.  For example, say I'm writing the 
Data.Complex module; there's a function in that module phase :: 
RealFloat a = Complex a - a.  So, how do you put this phase function 
into a type class?  Perhaps you could abstract away from the RealFloat 
and Complex bits, so you have a phase function which is generalised to 
work over a Num and an arbitrary data type instead; e.g. class Phase c 
where phase :: Num a = c a - a.  But what happens if, say, somebody 
adds a Moon data type, and they want to write a phase function which 
returns the phase of such a moon?  Phases of the moon certainly aren't 
Nums, nevermind the fact that you probably want to supply your moon 
phase's function with some sort of date as an extra parameter, which 
means the Phase type class isn't flexible enough.

Type classes are designed to provide a type-consistent interface to 
functions which perform different behaviour, unifying them as one 
function like + or == -- but it's designed to work for arbitrary types. 
 What I'm after is an interface for a function which may change 
depending on a primary type it's working with, which is almost the 
opposite to type classes.

--
% Andre Pang : trust.in.love.to.save
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-26 Thread ozone
On 27/02/2004, at 8:28 AM, Abraham Egnor wrote:

I think that this is a problem that can be solved with a simple 
convention
change, rather than a language extension - instead of appending type
names, I think it would be much better if modules simply used the 
short,
convenient, common names and expected the user to import them qualified
where overlap is a problem - in short, do exactly what DData does.  
It's
slightly more verbose than OO-style: Map.add map key value instead of
map.add(key, value); but I don't think that what OO does is a good
language design target.
This is exactly what was discussed in the thread before I barged in 
with per-type function namespaces, and it's not a good solution because 
of what Alastair has mentioned.  It's also not a good solution because 
I still have to type Map.add map instead of map.add: the type 
system already knows that map of type Map, so why should I have to 
qualify it even more by sticking a module name in front, and also 
encode the type name into my function because the module/namespace 
system isn't good enough to deal with this issue?

I also agree that what OO does is not a good language design target, 
but I do think that leverage type system to make programming nicer for 
you is a good design target :).  We're using a form of hungarian 
notation for function names, which is necessary because of a global 
namespace; OO people abolished this a long time ago.

Another random thought: what you describe sounds awfully similar to
typeclasses, just with a single function in each typeclass.
It's not the same as a single-function type class, for the reasons that 
I pointed out to Keith Wansbrough in an earlier email.

--
% Andre Pang : trust.in.love.to.save
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-02-26 Thread ozone
On 27/02/2004, at 1:13 PM, [EMAIL PROTECTED] wrote:

For example, say I'm writing the Data.Complex module; there's a
function in that module phase :: RealFloat a = Complex a - a.  So,
how do you put this phase function into a type class?  Perhaps you
could abstract away from the RealFloat and Complex bits, so you have a
phase function which is generalised to work over a Num and an
arbitrary data type instead; e.g. class Phase c where phase :: Num a
= c a - a.  But what happens if, say, somebody adds a Moon data
type, and they want to write a phase function which returns the phase
of such a moon?  Phases of the moon certainly aren't Nums, nevermind
the fact that you probably want to supply your moon phase's function
with some sort of date as an extra parameter, which means the Phase
type class isn't flexible enough.
Here's the code that does exactly as you wish:

{-# OPTIONS -fglasgow-exts #-}

import qualified Complex

class Phase a b | a - b where
  phase:: a - b
instance (RealFloat a) = Phase (Complex.Complex a) a where
phase = Complex.phase
data MoonPhase = P1 | P2 | P3 | P4 deriving Show

instance Phase Int MoonPhase where
phase x = if x `mod` 4 == 0 then P1 else P4
instance Phase MoonPhase (Int-Int) where
phase P1 x = x
phase P2 x = x+1
main = do
putStrLn $ show $ phase ( (1.0::Float) Complex.:+ 
(1.0::Float))
	  putStrLn $ show $ phase (0::Int)
	  putStrLn $ show $ phase P1 (2::Int)
Very, very nice Oleg :).  I'm glad to know that we can achieve such 
things using the existing type class mechanisms already.  However, this 
still doesn't solve the problem, because:

1) now I have to manually declare a class definition for every single 
function, and I have to declare it in advance before any module defines 
that function (most serious problem; see below),

2) I then have to declare instances of that type class for every 
function I define,

3) the type signature for phase reveals no clues about how to use that 
function.

So unfortunately, this is hardly a scalable solution.  The entire 
reason I came up with the idea is because if we use type classes to 
implement this sort of overloading, we have to know every single 
possible function that any module author will ever create, and declare 
classes for those functions in advance.  This is fine if you're 
declaring truly polymorphic functions which are designed from the start 
to be totally general, but it is not designed for functions which may 
do vastly different things and may contain totally different type 
signatures, but share the same name because that would be a sensible 
thing to do.  (e.g. the phase function mentioned above.)

With the per-type namespace separation I'm advocating, you do not need 
to know and declare in advance that each function will be overloaded, 
you simply write a FiniteMap.add function and a Set.add function, and 
you get a simpler form of namespace separation (or overloading) based 
on the first parameter that's passed to it.  It is a solution which is 
more _flexible_ than requiring type class definitions, and it is better 
than having hungarian notation for functions.  In fact, I think that, 
right now, if we replaced the current namespace separation offered by 
the hierarchical module system, and instead only had this sort of 
per-type namespace separation, things would still be better!

I realise my idea isn't very general in that it only allows this 
namespace lookup/overloading based on the type of a single argument 
parameter, and I think it would be possible with a bit more thinking to 
generalise it to work based on multiple arguments (e.g. via 
argument-dependent lookup, or whatnot).  But even in its current form, 
I honestly think it offers far more flexibility and would lead to 
cleaner APIs than is currently possible.

--
% Andre Pang : trust.in.love.to.save
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


[Haskell-cafe] Perl-ish =~ operator

2004-02-23 Thread ozone
In my effort to turn Haskell into a language more like Perl 
(muahaha)[1], I got a bit fed up and implemented something like Perl 
5's =~ binding operator (a.k.a. regex operator); I thought maybe 
somebody else here might find it useful.  Perl has the concept of 
'contexts': a function does something different depending on what type 
its caller expects back from the function.  Sounds like a perfect abuse 
of type classes, to me :).  Code follows:

---
{-# OPTIONS -fglasgow-exts #-}
{-  Need this for instance Foo [String] declarations -}
module PLRE where
-- Perl-Like Regular Expressions
import Text.Regex

-- Perl-Like =~ operator, which changes behaviour depending on its 
calling
-- context

class RegExContext a where
  (=~) :: String - String - a
instance RegExContext Bool where
  s =~ re = case matchRegex (mkRegex re) s of
Nothing - False
Just x - True
instance RegExContext [String] where
  s =~ re = case matchRegex (mkRegex re) s of
Nothing - []
Just x - x
boolContextTest string regEx =
  case string =~ regEx of
True - print True
False - print False
stringListContextTest string regEx =
  case string =~ regEx of
(a:x) - print (First match:  ++ a)
_ - error No subexpression matches
---
Some test output for you:

*PLRE boolContextTest foo ^f
True
*PLRE boolContextTest foo ^g
False
*PLRE stringListContextTest foo ^(.)
First match: f
*PLRE stringListContextTest goo ^(.)
First match: g
*PLRE stringListContextTest  ^(.)
*** Exception: No subexpression matches
Note that you have a fairly severe restriction if you want to use =~ in 
your code: the Haskell compiler must be able to determine a concrete 
type for the context that =~ is used in.  i.e. if stringListContextTest 
was defined as:

stringListContextTest string regEx =
  case string =~ regEx of
(a:x) - print a
_ - error No subexpression matches
The compiler can't concretise a type for 'a', and it'll complain about 
not having an instance for RegExContext [a] (which is fair enough).  
Even with this restriction, I'm sure it'll still be useful.  It 
shouldn't be a bit leap to define other Perl-ish operators in this 
fashion, such as !~, or even s/.../.  Have the appropriate amount of 
fun!

1. Actually, I wanted to turn Haskell into a language more suitable for 
text processing, but that doesn't sound as evil.

--
% Andre Pang : trust.in.love.to.save
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Perl-ish =~ operator

2004-02-23 Thread ozone
On 24/02/2004, at 1:30 AM, Andre Pang wrote:

In my effort to turn Haskell into a language more like Perl 
(muahaha)[1], I got a bit fed up and implemented something like Perl 
5's =~ binding operator (a.k.a. regex operator); I thought maybe 
somebody else here might find it useful.  Perl has the concept of 
'contexts': a function does something different depending on what type 
its caller expects back from the function.  Sounds like a perfect 
abuse of type classes, to me :).
And, just for kicks, here's Perl 6's smart match (~~) operator, which 
works much like ==, but in a more Do What I Mean! fashion, matching 
any type to any other type:

---
{-# OPTIONS -fglasgow-exts -fallow-undecidable-instances 
-fallow-overlapping-instances #-}

module SmartMatch where

import Text.Regex

class TruthValue a where
  truth :: a - Bool
instance TruthValue Bool where
  truth = id
instance TruthValue Int where
  truth 0 = False
  truth _ = True
instance TruthValue String where
  truth  = False
  truth _  = True
instance TruthValue a = TruthValue [a] where
  truth = all truth
class SmartMatch a b where
  (~~) :: a - b - Bool
instance Eq a = SmartMatch a a where
  a ~~ b = a == b
instance SmartMatch c d = SmartMatch d c where
  a ~~ b = b ~~ a
instance TruthValue a = SmartMatch Bool a where
  a ~~ b = a == truth b
instance SmartMatch String Regex where
  s ~~ re = case matchRegex re s of
Nothing - False
Just x - True
---
--
% Andre Pang : trust.in.love.to.save
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Perl-ish =~ operator

2004-02-23 Thread ozone
On 24/02/2004, at 1:30 AM, [EMAIL PROTECTED] wrote:

In my effort to turn Haskell into a language more like Perl 
(muahaha)[1], I got a bit fed up and implemented something like Perl 
5's =~ binding operator (a.k.a. regex operator); I thought maybe 
somebody else here might find it useful.  Perl has the concept of 
'contexts': a function does something different depending on what type 
its caller expects back from the function.  Sounds like a perfect 
abuse of type classes, to me :).
Bonus round: I've managed to hack up something which simulates Perl's 
s/// operator, and also something to emulate its /e modifier 
(evaluate), so that you can run a function over the resulting 
subexpression matches.  (You don't really _need_ the latter, because 
all you have to do is use the =~ operator in a [String] context and run 
your function over that, but hey, it's cool, and I get to abuse type 
classes even more :).

Now, =~ has to change its behaviour not only depending on its context, 
but also depending on what operation you do with it: matching, 
substitution, etc.  We differentiate each of the operations by giving 
them a different type: a simple match operation takes in a String (the 
regex to match), whereas substitution requires two strings: the string 
to match against, and the substitution string, i.e. (String, String).

---
{-# OPTIONS -fglasgow-exts #-}
--  Need this for instance Foo [String] declarations (look, don't even
--  need undecidable or overlapping instances :)
module PLRE where
-- Perl-Like Regular Expressions
import Maybe
import Text.Regex
-- Perl-Like =~ operator, which changes behaviour depending on its 
calling
-- context

class Bind op context where
  (=~) :: String - op - context
-- (=~) :: String - String - Bool
-- returns whether the regex matched or not
instance Bind String Bool where
  s =~ re = case matchRegex (mkRegex re) s of
Nothing - False
Just x - True
-- (=~) :: String - String - [String]
-- returns a list of subexpression matches
instance Bind String [String] where
  s =~ re = case matchRegex (mkRegex re) s of
Nothing - []
Just x - x
-- (=~) :: String - (String, String) - String
-- substitution: foo =~ (f, g) = goo
instance Bind (String, String) String where
  s =~ (re, sub) = case matchRegexAll (mkRegex re) s of
Nothing - []
Just (before, _, after, _) - before ++ sub ++ after
-- perl's /e modifier.  We expect a function that takes in an argument 
of
-- type [String] (and can output any type): in that argument, index 0 of
-- the list is the original string to match against, index 1 (if it
-- exists) is the first subexpression match, index 2 is the second
-- subexpression match, etc.

instance Bind (String, ([String] - context)) context where
  s =~ (re, fn) = case matchRegex (mkRegex re) s of
Just matches - fn (s:matches)
Nothing - fn [] -- or maybe this should be an error?
boolContextTest string regEx =
  case string =~ regEx of
True - print True
False - print False
stringListContextTest string regEx =
  case string =~ regEx of
(a:x) - print (First match:  ++ a)
_ - error No subexpression matches
---
For an example of how to use the /e-like operator:

PLRE foo =~ (^(..), \l - map Char.ord (l!!1) ) :: [Int]
[102,111]
i.e. it (vaguely) resembles something like $foo =~ s/^(..)/ord $1/;

One thing which would be really nice is to use implicit parameters for 
the subexpression match instead of passing the list of subexpression 
matches explicitly to the function, so that you could instead write:

PLRE foo =~ (^(..), map Char.ord ?_1 ) :: [Int]
[102,111]
So ?_n maps nicely on to Perl's $n match variable (or \n, if you're a 
sed foo).  I couldn't find any way for this to work, though, since 
implicit parameters aren't allowed in an instance declaration.

--
% Andre Pang : trust.in.love.to.save
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Making GHCi object files on MacOS

2003-12-09 Thread ozone
On 10/12/2003, at 3:35 AM, George Russell wrote:

The equivalent to GNU ld's --whole-archive option on Mac OS X is 
-all_load.
Thank you, that seems to work.  Now what should I do to prevent the 
GHCi linker
complaining about duplicate definitions for __module_registered 
(which
seems to be defined in some way in each object file)?
I don't have such duplicate definitions in my files ... producing a 
package with ghc-pkg -a works OK for me with Wolfgang Thaller's GHC 
6.0.1 build.  Is that how you're doing it, or are you trying to produce 
the GHCi object file manually?

--
% Andre Pang : trust.in.love.to.save
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC and Panther (Mac OS X 10.3)

2003-11-20 Thread ozone
On 20/11/2003, at 12:06 PM, Thomas Davie wrote:

Hi,
  I've just upgraded to OS X 10.3 and have been having some problems  
with ghc.

...

ghc -DUSE_READLINE=1 -L/sw/lib/ -lreadline -I/sw/include   -package  
lang -c -cpp -o  
/Users/tatd100/Documents/Work/Project/Tools/hmake-3.08/targets/ 
powerpc-Darwin7/obj/hmake/Compat.o Compat.hs
Compat.hs:1: parse error on input `#'
make[1]: ***  
[/Users/tatd100/Documents/Work/Project/Tools/hmake-3.08/targets/ 
powerpc-Darwin7/obj/hmake/Compat.o] Error 1
make: *** [targets/powerpc-Darwin7/hmake-ghc] Error 2

I'm guessing that there's some binary compatibility issues here...  
Could it be panther using gcc3.3?
This looks very much like a bug that a few other people have  
encountered with GHC and Panther; try adding

-pgmP gcc3 -E -traditional

to your commandline, which will use the gcc 3.1 pre-processor.   
(Apple's cpp-3.3 adds some extra line and debugging information to the  
output, which is harmless in C but interacts badly with Haskell  
syntax.)

--
% Andre Pang : trust.in.love.to.save
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Syntax extensions (was: RE: The Future of Haskell discussion at the Haskell Workshop)

2003-09-16 Thread ozone
On 11/09/2003, at 9:46 PM, Simon Marlow wrote:

I know that some of these problems can be addressed, at least in
part, by careful use of Makefiles, {-# custom pragmas #-}, and perhaps
by committing to a single tool solution.  But I'd like to propose
a new approach that eliminates some of the command line complexities
by integrating the selection of language extensions more tightly
with the rest of the language.
Initially I liked the idea, but now I'm not so sure (more about that
later). But first I'll point out that the situation isn't nearly as bad
as you make out.  In GHC, the approved way to add these flags is by
using a pragma to the source code, for example:
  {-# OPTIONS -fth -fffi #-}
  module Foo where
  ...
this in itself addresses most of your complaints.  Using a
compiler-independent syntax would address another one.  We're left 
with:
I'll second Simon on this suggestion.  I'm using {-# OPTIONS ... #-} 
pragmas on all my modules now, and it works great: no extra parameters 
need to be specified on the command-line, and I get only the extensions 
I want.  This seems to be more simple than the hierarchical module 
scheme, too.  (I'm a big fan of KISS.)

--
% Andre Pang : trust.in.love.to.save
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell