Re: [Haskell-cafe] Re: Double - CDouble, realToFrac doesn't work

2004-11-05 Thread MR K P SCHUPKE
My guess is because irrationals can't be represented on a discrete computer

Well, call it arbitrary precision floating point then. Having built in 
Integer support, it does seem odd only having Float/Double/Rational...

Keean.
..
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


template-haskell names in 6.3

2004-10-22 Thread MR K P SCHUPKE

I have now read most of the notes on template-haskell2, but I still
have a problem with naming (although I think my issues with types
are adequately dealt with by the '' notation.

I wish to create a declaration in template haskell, where the funtion
name is supplied: something like:

$(label myLabel)

However I wish the reference to this label to be globally specific
to the generated instance... an example of this would be a function
that prints its reified name:

$(example myLabel) would splice:

myLabel :: String
myLabel = This_module.myLabel

mkName only returns the 'local' namem 
how can I get a global name from a string?

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


TH2 bug

2004-10-22 Thread MR K P SCHUPKE

Just reporting a bug, taking types using '' works fine for:

''Int
''[]

But when you try:

''(-)

you get:

No match in record selector TyCon.algTcRhs

Please report it as a compiler bug to [EMAIL PROTECTED],
or http://sourceforge.net/projects/ghc/.


Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: deriving...

2004-10-20 Thread MR K P SCHUPKE
As posted on this list, there is template-haskell code to do:

$(derive [| data Foo = Foo |])

You can also get the type of Foo in TH by doing:

dummy :: Foo
dummy = undefined
$(derive2 dummy)

and the code for derive2 reify's the argument, which then gives the
reflected type... so the example code given for the first form can
be adapted to the second use.

As you can already do this in TH, why introduce another extension?

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Template Haskell...

2004-10-20 Thread MR K P SCHUPKE

What replaces 'gensym' in GHC 6.3?

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Template Haskell...

2004-10-20 Thread MR K P SCHUPKE

Thanks for the URL... I have realised I jumped the gun saying the derivation can be 
done in template-haskell... there is one small problem:

$(derive [t| SomeConstructor a b |])

passes the constructor to derive... is there any way to get the type information
for some type? You can do

$(derive [d| data X a b = X1 a b |])

Is there any way to get the same information from something like:

$(derive2 [T| X a b |])

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: deriving...

2004-10-16 Thread MR K P SCHUPKE
Check out Ulf Norell's IOHCC submission, his DeriveData.hs module does this,

Do you have a link?

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


deriving...

2004-10-13 Thread MR K P SCHUPKE

What is the situation with deriving?

Some instances can be derived automatically for both data/newtype (built in)?

Some instances cen be derived automatically for newtype (any)?

You used to be able to define functions useing {|+|} and {|*|} (or similar)
that could be derived for both data and newtype.

What is the current status, which methods are supported, and will be
supported going forward.

I ask this because looking at the code in the compiler it seems very
difficault to extend. It would be to specify how to derive new instances
once and for all...

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: deriving...

2004-10-13 Thread MR K P SCHUPKE
look at the user manual.

Okay, I see the Generic type class stuff does not support multi
parameter type classes. I guess I am stuck - any suggestions as to
how best do this? 

I wish to be able to derive type level labels for datatypes, like  
the following: 

data Fred a = Fred a deriving TTypeable

generates the instance:

instance TTypeable a al = TTypeable (Fred a) (NCons (N3 (N4 (N5 Nil))) (TCons al Nil))

where (N3 (N4 (N5 Nil))) is the result of a hash function on the name Fred.

I have looked at TcDeriv but I don't know enough of the compiler internals to see
how this would be added to the current implementation... Can you give me some pointers
on how to do this?

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


deriving

2004-10-08 Thread MR K P SCHUPKE

How is deriving coded in ghc. For example the Typeable class, when in
the compilation sequence is this expanded? Which modules do this, and 
which functions?

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


ppr styles...

2004-09-06 Thread MR K P SCHUPKE

If I print out HsSyn types with pprTrace, I get:

test{v} () = id{v} ()

or something similar (depending on the declaration). Is there
any way I can get it to print out the raw data structure?

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: ppr styles...

2004-09-06 Thread MR K P SCHUPKE
Would it cause me any problems if I added deriving Show to all the 
types in compiler/hsSyn? (Can't think of a problem here... is there any
reason why this is not done by default? - It is really handy if trying to
pattern match on code syntax to be able to see what abstract syntax is 
generated by certain code)

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: ppr styles...

2004-09-06 Thread MR K P SCHUPKE
I have added some of the required deriving clauses, however I now
get lots of warnings about:

Bad eta expand
__coerce ()
(CmmParse.zgzg {- v rnrp -}
   @ ()
   @ ()
   (__coerce CmmParse.ExtCode {- tc rB2 -} happyzuxzu1 {- v a1B9 -})
   (__coerce CmmParse.ExtCode {- tc rB2 -} happyzuxzu2 {- v a1B8 -})
   (__coerce CmmParse.Env {- tc rB6 -} eta {- v skLC -}))
()

Is this something I should worry about?

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


boot files...

2004-09-06 Thread MR K P SCHUPKE

I need to change the boot .hi files for TypeRep, to include
the derivied show instance for TyThing, what is the format?

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: boot files...

2004-09-06 Thread MR K P SCHUPKE
Yes, it might be easier to elaborate the ppr instances... That
way I only have to modify instances I am interested in.

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Type reps inside GHC...

2004-09-03 Thread MR K P SCHUPKE

Playing with HsSyn types (like HsModule)... I have got down to the
definition level like:

Sig id = Sig (Location name) (LHsDecl name)

what type is name? Presumably it can be a range of types, 
what are valid types for name? 

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


pprTrace

2004-09-02 Thread MR K P SCHUPKE

When writing code in the compiler, how do you use pprTrace?

I want to print out the type of a SigD from HsDecl?

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Extra parse stage...

2004-08-25 Thread MR K P SCHUPKE

I wish to add some extended syntax to type definitions,
assuming I modify the parser files and associated datatypes
to carry the extra information, is there a convenient place
to insert a pre-parse (before type-checking) to convert the
syntax extensions to regular haskell?

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC and MPTCs

2004-08-25 Thread MR K P SCHUPKE
Try type annotations:

new_point (s::s) t b : interleave (next_state s::s) bs (t:ts)


Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Bug in GHC when compiling with -O ?

2004-08-17 Thread MR K P SCHUPKE
You will have to give both the errors and the source code...
I have done quite a bit with classes and GHC's constraint
inferance is pretty good. 

The chances are you really do need to add some extra 
constraints...

(by the way if you are working with heterogeneous collections,
you may be interested in out paper, http://www.cwi.nl/~ralf/HList
)

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: isEmptyChan, System.Posix.Signals

2004-08-16 Thread MR K P SCHUPKE
I thought NT and more recent was Posix compliant... Surely it should 
support posix signals?

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Announce: hs-plugins-0.9.6

2004-08-16 Thread MR K P SCHUPKE
There is a portable System.Process library here:

On that note, perhaps all signals on unix should be
set to ignore, so if you are writing cross platform
code you don't have to do special stuff with say 
sigPIPE for example

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Lazy type-class resolution

2004-08-13 Thread MR K P SCHUPKE
Yes, lazy type-class resolution is a known GHC feature - and in my
opinion much superior to Hugs stict type class resolution. Hugs
can get confused with overlapping instances and will choose the
wrong instance because it commits too early. GHC does not suffer
from this.

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Closed Classes...

2004-08-13 Thread MR K P SCHUPKE

If I wanted to experiment with instance selection, which part of
GHC do I want to be looking at?

Keean
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


GHC CVS build...

2004-08-13 Thread MR K P SCHUPKE

just checked out the CVS ghc to play with instance
resolution - however:

fptools/mk/config.h.in

seems to be missing and nothing can be built.

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Closed Classes...

2004-08-12 Thread MR K P SCHUPKE

Been having a bit of a discussion in the Cafe... Just wondered what
GHC specific issues would be involved with assuming all classes are closed.

I am thinking that there is no real dis-advantage to considering all
classes closed within their current context (IE all the imports to
the current module).

It seems to me that the argument about breaking code is wrong, as 
any changes to modules not imported into this module cannot have
any affect on the code in this module. The only changes that
can affect this module are changes to modules imported into
this module - which of course can break things in many ways 
(like changing the type of a function)... In other words when
the instances visible in a module change - all modules importing
that module need to be recompiled (which is what happens when you
use 'make' anyway).

Can somebody either convince me their is a real problem with 
the 'closed' assumption, otherwise can GHC be changes to 
do this? Maybe an intermediate step would be to have a command
line flag (-fall-closed ?)

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: type synonyms in instances...

2004-07-16 Thread MR K P SCHUPKE
Actually I lied.  You need the -fglasgow-exts flag.

Yes, I should have tried it before I posted, I just remembered reading
in the manual that type synonyms were excluded... But on re reading
it actually said partial applications of type synonyms were excluded,
which does not affect what I wanted to do...

It just tidies up a few long instances.

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


type synonyms in instances...

2004-07-07 Thread MR K P SCHUPKE

Is there any chance of enabling type synonyms in instance declarations.
I remember a posting where is was stated that there was no technical 
reason for not being able to do this.

Could we perhaps have a command line switch to enable this...

For example, I think the following:-

instance (HList e HNil) where ...

is more readable as:

type HSingleton e = HCons e HNil

instance (HSingleton e) where ...

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Socket Options

2004-06-28 Thread MR K P SCHUPKE
What would happen if a timeout occurs in the _socket_ level?

I believe a (unix) socket level problem (including remote server
closing the connection unexpectedly) results in a Posix SigPIPE.

Is you set the default action to ignore:

installHandler sigPIPE Ignore Nothing

Then it gets converted to an asynchronous exception... that means
you have to be extremely careful with your 'catch' clauses so
as to ensure that system resources allocated to the socket get
cleaned up. 

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Socket Options

2004-06-28 Thread MR K P SCHUPKE
If you fork a thread to handle each connection the async
exception is thrown to the (Haskell) thread which is
performing IO on the socket when it happens. 

(the ignore means ignore the signal the default action is
to terminate the program)

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Finalizers and FFI

2004-06-10 Thread MR K P SCHUPKE
I don't see why GHC can't have a 'callAllOutstandingFinalizers' call
as part of _exit() or something...

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: F#

2004-06-01 Thread MR K P SCHUPKE
Can't help but comment...
 
Purely functional languages like Haskell are excellent
within certain niches, but non-trivial problems exist
with language interoperability between lazy and strict
languages.
  
I don't wish to appear to be too harsh on Microsoft, (after all
they are supporting work on GHC) - but they tend to ignore all non-Microsoft
solutions... deliberatly (its a marketing thing). So when you read the
above - you have to substitute Microsoft languages for strict
languages for it to really make sense ... after all C is the
predominant language of the day, and I have found it relatively
easy to do C FFI stuff, okay so you have to allocate and deallocate
memory, but you would have to do that in C anyway. It seems to
me the author of that quota had languages like Visual-Basic
in mind. Here the work of marshalling is pretty complex compared
to usual Visual-Basic fare...

The other area (again MS specific) that F# has better interoperability,
is .NET . F# (notice similarity to C#) is a funtional language within
the .NET framework - hence supports the 'COM' style interface within
the language primitives, just like C# does. This means coding a .NET
component in F# is trivial - In haskell its still pretty hard-core
(its hard even in C hence the prevelence of visual-toolkits on the MS
platform - and also the eventual development of C#)

The only way the author of this comment can be persuaded to delete it
I think is if Haskell were to have a neat .NET component interface, unfortunately
Haskell's class system is not up to incorporating OO hierachies like .NET
without some changes...

I think however the complexities mentioned relate to .NET / COM style
object systems, and not traditional languages like C. Maybe we should
ask for the quote to be revised to: interoperability between lazy and 
component based object hierachies ?

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Overlapping, undecidable, incoherent -- or worse?

2004-05-21 Thread MR K P SCHUPKE
I have seen very compact Prolog implementations in Haskell, and I 
also know that constraints, modelled by CHRs can be evaluated directly
in Prolog. Why not just bolt one of these compact Prologs onto the
compiler, and just feed it the facts and rules...

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: F#

2004-05-21 Thread MR K P SCHUPKE
 but unfortunately some simple programming exercises can quickly turn
 into problems that require a PhD. to solve.

Of course you could say that the excersise is not actaully as simple
as you believe, and other languages will let you get away with stuff
you really shouldn't be doing.

A good example of this is threads. There are apparently very few programmers
that can do threads well, I heard of one survey that stated most programming
shops only have one 'threads expert' and problems inevitably get referred to
them. 

Haskell solves a lot of the problems you have in dealing nicely with threads
in other languages (no side effects - built in channels and MVars so no
visible mutexes). #

One of the biggest problems in software is dealing with complexity, so
anything that helps sort this out is a plus... 

Most large software projects are delivered late or not working due to 
complexity. I guess the person that wrote that article was thinking
about 'scripting' rather than programming (as in visual basic style
stuff) - Well thats my opinion at least...

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Overlapping, undecidable, incoherent -- or worse?

2004-05-20 Thread MR K P SCHUPKE
I don't know whether this was apparent, but only the instance
pattern is used in determining which instance to use, so 
PO a is the same as PO a ... you need to make them different
otherwise they don;t just overlap they are identical. 
the left-hand-side of the = play no part in instance selection.

That is why I suggested using new types. (infact it is your only option)

Even priority would not help here, as the instances are identical.
(there is a priority, in that if the instances are overlapping
the most specific is used, IE choosing between (PO a) and (PO Int)
PO Int wins is 'a' is an Int.

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Overlapping, undecidable, incoherent -- or worse?

2004-05-20 Thread MR K P SCHUPKE
That's not the notion of priority I was referring to.

Any type of priority would not help. As I said then the instance heads
are identical (PO a) and (PO a) - no kind of priority will help
differenciate the,

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Overlapping, undecidable, incoherent -- or worse?

2004-05-20 Thread MR K P SCHUPKE
I wasn't talking about _any_ notion of ordering of instance heads;  I
said that prioritising instance _declarations_ themselves, explicitly,
by 'name' would suffice.

How does that help... if you name the instances differently are they
not just ordinary functions, as they would no longer be overloaded?

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Overlapping, undecidable, incoherent -- or worse?

2004-05-20 Thread MR K P SCHUPKE
I don't think you get it... naming does not help, the problem is the
compiler cannot distinguish between the instances.

The alternative to the current situation is to take into account the
dependancies of instances when selecting. The problem here is that
the compiler may select an instance, evaluate its dependencies, only
to discover somewhere further on that the dependencies cannot be met.
At this point it has to backtrack (reverse its previous decisions) and
try another instance. This effectively means implementing a Prolog
style solver in the compiler - which leads to the further problems of
the compiler possible not terminating (ie taking forever to not 
compile something)...

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Overlapping, undecidable, incoherent -- or worse?

2004-05-20 Thread MR K P SCHUPKE
that is not the case with -fallow-undecidable-instances ... as far as
I understand it , ghc never considers the dependancies when selecting an
instance. If you don't think so you will need to show me an example where
it clearly does... as I haven't seen one yet (but just because I haven't
seen it doesn't mean its not possible),,,

IMHO, things should either stay as they are (only instance heads supported)
or it should switch to full Prolog style backtracking.

Given who 
I mean, given two instances like:

instance a b c
instance d e f

there is no way to tell between them... if you said choose a in preferenc
'a' would be chosen all the time. 

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Overlapping, undecidable, incoherent -- or worse?

2004-05-20 Thread MR K P SCHUPKE
I think you should read the GHC manual (assuming it is up to date
and undecidable instances means what it says it does, the difference
is...

Without undecidable instances at least one type in the instance
must not be a type variable. 

With undecidable instances you can have a default-instance (all
type variables) or a class synonym (one instance - all type variables)

Thats it... Neither GHC nor Hugs pay any attention to the 
dependancies when choosing which instance to use. The
dependancies are only considered after the decision has
been irrevocably made. If the dependancies don't hold, the
only option the compiler has is to bail out with a compile
time error.

Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


GHC CVS refusing connections...

2004-04-22 Thread MR K P SCHUPKE

tried to update to update GHC from CVS today, with CVSROOT=
:pserver:[EMAIL PROTECTED]:/cvs

but got the error:
cvs [login aborted]: connect to glass.cse.ogi.edu(129.95.44.145):2401 failed: 
Connection refused


Is it my ISP, or is everyone having the same problem?

Regards,
Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Haskell performance

2004-03-18 Thread MR K P SCHUPKE

How can you take the results of a comparison like that seriously:

For example the reverse file test, here is the Haskell actually used:

main = interact $ unlines . reverse . lines


and here is the C:


/* -*- mode: c -*-
 * $Id: reversefile.gcc,v 1.10 2001/07/20 17:20:32 doug Exp $
 * http://www.bagley.org/~doug/shootout/
 * from Brad Knotwell
 */

#include stdio.h
#include stdlib.h
#include string.h
#include unistd.h

#define MAXREAD 4096

int main(int argc, char *argv[]) {
int nread, len = 0, size = (4 * MAXREAD);
char *cp, *buf = malloc(size + 1);

while((nread = read(0,(buf+len),MAXREAD))  0) {
len += nread;
if(MAXREAD  (size - len)) {
size = 1;
if((buf = realloc(buf,size+1)) == NULL)
return(fprintf(stderr,realloc failed\n),EXIT_FAILURE);
}
}

if(nread == -1) return(fprintf(stderr,read\n),EXIT_FAILURE);

for (cp = buf+len-1; cp != buf; --cp,nread++)
if ('\n' == *cp) {
fwrite(cp+1,nread,1,stdout);
nread = 0;
}

fwrite(cp,nread+1,1,stdout);
free(buf);
return(EXIT_SUCCESS);
}


Firstly, which of these is more likely to contain an error. A wrong program
scores infinity on the time scale, so Haskell is infinitely faster than a wrong
C program.

Secondly, The C program is using buffers, the Haskell program could use raw IO
and buffers too. If it did it would ba a lot faster, and use about the same
memory as the C code...

In my experiance poor Haskell performance is usually due to not understanding
how the language works (for example head/tail are fast, init/last are slow), or
not using the equivalent techniques in Haskell. To do the equivalent of the C
you could use: http://www.haskell.org/~simonmar/io/System.IO.html

Regards,
Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


type problem

2004-03-15 Thread MR K P SCHUPKE

Is there any way to insist that two types are different? For example

f :: NotSame a b = a - b

Regards,
Keean Schupke.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Polymorphic lists...

2004-03-10 Thread MR K P SCHUPKE

Hi Oleg, I like the polymorphic list indexed by Ints... there
do seem to be a couple of differences between this and the list
indexed by natural numbers.

The list indexed by integers cannot determine the type of the
return value through induction on the class... in other words 
it cannot determine the return type of the lookup function
until runtime: you can see this in the class instance for 'tke'

 instance (TH a (a,b), TH W b) = TH W (a,b) where
 tke (W 0) th@(h,t) f = f h th
 tke (W n) (h,t) f = tke (W$ n-1) t f

On the other hand indexing by natural numbers allows the compiler
to know the return type (and avoid the use of existentials)
because it is determined at compile time... you can see this because
the recursion termination is done by the type signatures in the instance
not the pattern guards of the function.

instance Relation r = RIndex Zero (a `RCons` r) a where
   rIndex Zero (x `RCons` _) = x
instance RIndex Idx r b = RIndex Idx (a `RCons` r) b where
   rIndex (Suc n) (_ `RCons` xs) = rIndex n xs

It looks like most of this stuff has been done before... but I don't think
there is any of it in the ghc libraries. I needed this code for a real
application, and could not find anything suitable so I rolled my own.

What do people think - is there a case for getting this stuff in the libs,
should we write a functional pearl? does anyone have any comments about
the code I posted, or how it could be improved?


To finish, here are some new definitions for map,zip and unzip

class Relation r = RMap t r where
   rMap :: t - r - r
instance RMap t RNil where
   rMap _ RNil = RNil
instance (RMapFn t a,RMap t r) = RMap t (a `RCons` r) where
   rMap t (x `RCons` xs) = rMapFn t x `RCons` rMap t xs

class RMapFn t a where
   rMapFn :: t - a - a

data RMapId = RMapId
instance RMapFn RMapId a where
   rMapFn RMapId a = a


class (Relation r1,Relation r2,Relation r3) = RZip r1 r2 r3 | r1 r2 - r3 where
   rZip :: r1 - r2 - r3
instance RZip RNil RNil RNil where
   rZip _ _ = RNil
instance RZip r1 r2 r3 = RZip (a `RCons` r1) (b `RCons` r2) ((a,b) `RCons` r3) where
   rZip (x `RCons` xs) (y `RCons` ys) = (x,y) `RCons` rZip xs ys


class (Relation r1,Relation r2,Relation r3) = RUnZip r1 r2 r3 | r1 - r2 r3 where
   rUnZip :: r1 - (r2,r3)
instance RUnZip RNil RNil RNil where
   rUnZip _ = (RNil,RNil)
instance RUnZip r1 r2 r3 = RUnZip ((a,b) `RCons` r1) (a `RCons` r2) (b `RCons` r3) 
where
   rUnZip ((x,y) `RCons` xys) = (x `RCons` xs,y `RCons` ys) where
  (xs,ys) = rUnZip xys


and finally a lookup that indexes by the left type of a pair and returns the right 
type  value
stored in a polymorphic list:

class Relation r = RLookup r l v | r l - v where
   rLookup :: r - l - v
instance Relation r = RLookup ((l,v) `RCons` r) l v where
   rLookup ((_,v) `RCons` _) _ = v
instance RLookup r l v = RLookup ((l',v') `RCons` r) l v where
   rLookup (_ `RCons` r) l = rLookup r l


Regards,
Keean Schupke.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Polymorphic lists...

2004-03-10 Thread MR K P SCHUPKE


This is the latest varient. Let me know whether you guys find this
interesting, as I am coding what I need for a practical application,
it may be tedious for you... I am still of the opinion that some
kind of polygenious list (or maybe heteromorphic?) would be good in
the standard libraries, whether it my code, someone elses or some
combination.

My initial feeling would be to standardise our function , class and
type naming so the different kinds of list/set can be put into the
same codebase, possibly aimed at being Data.PolyLists, also what is
required to get these in the library - just the code, neat code,
a report, or some kind of proposal ?


infixr 1 `MCons`
data MNil = MNil deriving Show
data MCons l a r = a `MCons` r deriving Show

class MRelation r
instance MRelation MNil
instance MRelation r = MRelation (MCons l a r)


This is a labelled list. It uses a phantom type to label
each node, but it theoretically needs no storage for the label...

Standard list functions operate as before, and ignore the phantom
type.


class MRelation r = MList r where
   mHead :: MCons l a r - a
   mTail :: MCons l a r - r
   mIsEmpty :: r - Bool
instance MList MNil where
   mHead (x `MCons` _) = x
   mTail (_ `MCons` _) = MNil
   mIsEmpty MNil = True
instance MList r = MList (MCons l a r) where
   mHead (x `MCons` _) = x
   mTail (_ `MCons` xs) = xs
   mIsEmpty (_ `MCons` _) = False


I have the usual suspects fold/map/zip/unzip, and natural
number lookup coded. This is the nice touch though, an indexed
lookup on the phatom type, which finds the Nth occurance of a
given type in the list:


class (MRelation r,Nat n) = MLookup l n r a | l n r - a where
   mLookup :: r - l - n - a
instance MRelation r = MLookup l Zero (MCons l a r) a where
   mLookup (x `MCons` _) _ Zero = x
instance MLookup l n r b = MLookup l (Suc n) (MCons l a r) b where
   mLookup (_ `MCons` xs) l (Suc n) = mLookup xs l n
instance MLookup l n r b = MLookup l n (MCons m a r) b where
   mLookup (_ `MCons` xs) l n = mLookup xs l n



heres an example:



data Name = Name
data Size = Size
data Weight = Weight

test = MCons Name String
(MCons Size Int
(MCons Weight Float
MNil))
test = Box `MCons` 3 `MCons` 1.1

putStrLn $ show $ mLookup test Name zero
putStrLn $ show $ mLookup test Size zero
putStrLn $ show $ mLookup test Weight zero

putStrLn $ show $ mLookup (test `mProduct` test) Name one 
putStrLn $ show $ mLookup (test `mProduct` test) Weight zero



These last two show how to access the labels from the right
and left sides of the product when some/all domains have the
same name.


Regards,
Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Polymorphic lists...

2004-03-09 Thread MR K P SCHUPKE
I did not know about Oleg's posting, as I originally said, I based my implementation on
a paper by Conor McBride. Oleg is addressing the question of type safe casting, rather
than generic storage, so his code is a bit different. Infact his class:

 class TypeSeq t s where
 type_index:: t - s - Int
 fetch:: t - s - t
 alter:: t - s - s

 instance (PList Cons t r) = TypeSeq t (Cons t r) where
 type_index _ _ = 0
 fetch _ (Cons v _) = v
 alter newv (Cons v r)  = Cons newv r

 instance (PList Cons t' r', TypeSeq t r') = TypeSeq t (Cons t' r') where
 type_index v s = 1 + (type_index v $ cdr s)
 fetch v s = fetch v $ cdr s
 alter newv (Cons v' r') = Cons v' $ alter newv r'

This stores unique types in a list that can be indexed by their types. Actually last 
night (before I read this code) I came up with something similar:

data MNil = MNil deriving (Show,Data,Typeable)
data MCons l a r = MCons l a r deriving (Show,Data,Typeable)

class MLookup l r a | l r - a where
   mLookup :: r - l - a
instance MLookup l (MCons l a r) a where
   mLookup (MCons _ x _) _ = x
instance MLookup l r b = MLookup l (MCons m a r) b where
   mLookup (MCons _ _ xs) l = mLookup xs l


This is indexed by a unique type, but stores a second independant
type. The allows a kind of static finite map, which is pretty cool!
Here's an example:

data TmId = TmId
data TmVal = TmVal
data TmFloat = TmFloat
data TmName = TmName

testMap :: MCons TmId Int
(MCons TmVal String
(MCons TmFloat Float
(MCons TmName String
MNil)))

testMap = MCons TmId 1
$ MCons TmVal Hello
$ MCons TmFloat 1.2
$ MCons TmName World
MNil

main :: IO ()
main = do
putStrLn $ show $ testMap `mLookup` TmId
putStrLn $ show $ testMap `mLookup` TmVal
putStrLn $ show $ testMap `mLookup` TmFloat
putStrLn $ show $ testMap `mLookup` TmName

Index types don't need to be unique, the first match from the
head of the list will be returned. No match will result in a 
compile time error.

Regards,
Keean Schupke.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Polymorphic lists...

2004-03-09 Thread MR K P SCHUPKE

I have written a first attempt at a fold function for the heterogenious list: 

class RFold i r where
   rFold :: (forall a . a - i - i) - i - r - i
instance RFold i RNil where
   rFold f i RNil = i 
instance RFold i r = RFold i (a `RCons` r) where
   rFold f i (x `RCons` xs) = f x (rFold f i xs)

This works providing the folded 'op' has the type: forall a . a - i - i
which means it does not work for functions like show :: forall a . Show a = a - i - 
i
as the types are different. I have not figured out a way to make it accept a 
constraint 
like Show for example. Here is an example:

length = rFold (\_ - (+1)) 0 relation

The use of such a function seems limited, if constraints like Show cannot be used, as
most useful applications of fold would require some kind of class membership for 
example:

string = rFold shows  relation

This fails to compile because shows has type:

shows :: forall a . Show a = a - i - i

but fold expects

op :: forall a . a - i - i

Regards,
Keean Schupke.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Polymorphic lists...

2004-03-09 Thread MR K P SCHUPKE

I have written a first attempt at a fold function for the heterogenious list: 

class RFold i r where
   rFold :: (forall a . a - i - i) - i - r - i
instance RFold i RNil where
   rFold f i RNil = i 
instance RFold i r = RFold i (a `RCons` r) where
   rFold f i (x `RCons` xs) = f x (rFold f i xs)

This works providing the folded 'op' has the type: forall a . a - i - i
which means it does not work for functions like show :: forall a . Show a = a - i - 
i
as the types are different. I have not figured out a way to make it accept a 
constraint 
like Show for example. Here is an example:

length = rFold (\_ - (+1)) 0 relation

The use of such a function seems limited, if constraints like Show cannot be used, as
most useful applications of fold would require some kind of class membership for 
example:

string = rFold shows  relation 

This fails to compile because shows has type:

shows :: forall a . Show a = a - i - i

but fold expects

op :: forall a . a - i - i

Regards,
Keean Schupke.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Polymorphic lists...

2004-03-09 Thread MR K P SCHUPKE
Ok... After playing with these types, I could not get it to work with 
the satFold
below. However it did inspire me to try something else, and this seems 
to work
quite well.

First redefine the RFold function to use RFoldFn class as its operator. 
Then create
instances of RFoldFn to do what you like. The clever bit is the use of 
an abstract
data-type to select which instance to use.



class RFold t i r where
  rFold :: t - i - r - i
instance RFold t i RNil where
  rFold _ i RNil = i
instance (RFoldFn t a i,RFold t i r) = RFold t i (a `RCons` r) where
  rFold t i (x `RCons` xs) = rFoldFn t x (rFold t i xs)
class RFoldFn t a i where
  rFoldFn :: t - a - i - i


Here's some examples:

data ShowFn = ShowFn
instance Show a = RFoldFn ShowFn a String where
  rFoldFn ShowFn x y = shows x y
putStrLn $ show $ rFold ShowFn  r

data SumFn = SumFn
instance Num i = RFoldFn SumFn a i where
  rFoldFn SumFn _ s = 1 + s
putStrLn $ show $ rFold SumFn 0 r

I think this is pretty neat, and the mechanism fits in well with how the 
rest
of the module works...

   Regards,
   Keean Schupke.
Hal Daume III wrote:

Though I haven't tried it, the explicit 'Sat' dictionary representation
would probably work here, something like:
 

data ShowD a = ShowD { showD :: a - String }
  -- our explicit dictionary for show, would need one of
  -- these for each class we care about
-- the satisfaction class:
class Sat t where dict :: t
-- an instance for show:
instance Show a = Sat (ShowD a) where dict = ShowD { showD = show }
instance Sat (ShowD a) = Show a where show = showD dict
   

manually generating datatypes and instances is tedious, but could easily 
be automated.  you should be able to use this to write:

 

satFold :: forall c b . Sat c b =
  (forall a . Sat (c a) = a - i - i) -
  b - r - b
   

or something similar.  probably worth a shot.

 

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Polymorphic lists...

2004-03-08 Thread MR K P SCHUPKE
I needed a list which could handle items of different types for the 
database code I am writing. I have written a module implementing such a 
list based on dependant types (from Conor McBride: Faking It; Simulating 
Depandant Types in Haskell). Although McBride does not mention 
lists/vectors with items of differing types, the solution to 
implementing them came from his 'nthFront' function for re-arranging the 
order of arguments to a function.

Any type can be inserted into the list, which supports 
head/tail/init/last, as well as indexed lookup, and a cartesian-product 
(concatenating two lists together). I have included fromTuple/toTuple as 
well.

This seems quite a useful construct, and if there is nothing similar in 
the standard libraries at the moment, do you think this is worth including?

   Regards,
   Keean Schupke.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Polymorphic lists...

2004-03-08 Thread MR K P SCHUPKE

Didn't know If I should post it straight away... its quite long and I dont do
attachments (well not If I can help it. I am aware Dynamic can model heterogenious 
lists
(thanks for correct terminology) - but I need static typing. Thats the clever thing 
about
this code - the list is heterogenious but statically typed.

So... for your perusal - and If its not up to being included in the libraries I would
value any comments/code review for my own edification.

The module is called Relation as I am modelling Relational Algebra... but if anyone 
can
think of a better name...

First some examples:

putStrLn $ show (rIndex two rel1) -- show the third item in rel1
putStrLn $ show (rHead r)
putStrLn $ show (rTail r)
putStrLn $ show (rLast r)
putStrLn $ show (rInit r)
putStrLn $ show (r `rEnqueue` TEST3) -- insert the string into the last (not head) 
position
putStrLn $ show ((3 :: Int) `RCons` r) -- insert the Int into the head of the list
r = toTuple (( 1.1 :: Double) `RCons` (fromTuple (hello,1,World)))


And the code:

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

module Lib.DBC.Relation where

--
-- (c) 2004 Keean Schupke, All Rights Reserved.
--

data Zero = Zero deriving Show
data Suc n = Suc n deriving Show

class Nat n
instance Nat Zero
instance Nat n = Nat (Suc n)

zero :: Zero
zero = Zero

one :: Suc Zero
one = Suc zero

two :: Suc (Suc Zero)
two = Suc one

three :: Suc (Suc (Suc Zero))
three = Suc two

four :: Suc (Suc (Suc (Suc Zero)))
four = Suc three

five :: Suc (Suc (Suc (Suc (Suc Zero
five = Suc four

--

infixr 1 `RCons`
data RNil = RNil deriving Show
data RCons a r = a `RCons` r deriving Show

--

class Relation r where
   rHead :: a `RCons` r - a
   rTail :: a `RCons` r - r
   rIsEmpty :: r - Bool
instance Relation RNil where
   rHead (x `RCons` _) = x
   rTail (_ `RCons` _) = RNil
   rIsEmpty RNil = True
instance Relation r = Relation (a `RCons` r) where
   rHead (x `RCons` _) = x
   rTail (_ `RCons` xs) = xs
   rIsEmpty (_ `RCons` _) = False

class RLast r a | r - a where
   rLast :: r - a
instance RLast (a `RCons` RNil) a where
   rLast (x `RCons` RNil) = x
instance RLast r b = RLast (a `RCons` r) b where
   rLast (_ `RCons` xs) = rLast xs

class RInit r1 r2 | r1 - r2 where
   rInit :: r1 - r2
instance RInit (a `RCons` RNil) RNil where
   rInit (_ `RCons` RNil) = RNil
instance RInit (b `RCons` r1) r2 = RInit (a `RCons` b `RCons` r1) (a `RCons` r2) where
   rInit (x `RCons` xs) = x `RCons` rInit xs

class REnqueue r1 r2 a | r1 a - r2 where
   rEnqueue :: r1 - a - r2
instance REnqueue RNil (a `RCons` RNil) a where
   rEnqueue RNil y = y `RCons` RNil
instance REnqueue r1 r2 b = REnqueue (a `RCons` r1) (a `RCons` r2) b where
   rEnqueue (x `RCons` xs) y = x `RCons` rEnqueue xs y

class (Nat n,Relation r) = RIndex n r a | n r - a where
   rIndex :: n - r - a
instance Relation r = RIndex Zero (a `RCons` r) a where
   rIndex Zero (x `RCons` _) = x
instance RIndex n r b = RIndex (Suc n) (a `RCons` r) b where
   rIndex (Suc n) (_ `RCons` xs) = rIndex n xs

infixl 2 `rProduct`
class (Relation r1,Relation r2,Relation r3) = RProduct r1 r2 r3 | r1 r2 - r3 where
   rProduct :: r1 - r2 - r3
instance RProduct RNil RNil RNil where
   rProduct RNil RNil = RNil
instance Relation r = RProduct RNil r r where
   rProduct RNil r = r
instance RProduct r1 r2 r3 = RProduct (a `RCons` r1) r2 (a `RCons` r3) where
   rProduct (x `RCons` xs) y = x `RCons` (xs `rProduct` y)

--

class Relation r = RTuple t r | t - r , r - t where
   fromTuple :: t - r
   toTuple :: r - t

instance RTuple (a,b) (a `RCons` b `RCons` RNil) where
   fromTuple (a,b) = a `RCons` b `RCons` RNil
   toTuple (a `RCons` b `RCons` RNil) = (a,b)

instance RTuple (a,b,c) (a `RCons` b `RCons` c `RCons` RNil) where
   fromTuple (a,b,c) = a `RCons` b `RCons` c `RCons` RNil
   toTuple (a `RCons` b `RCons` c `RCons` RNil) = (a,b,c)

instance RTuple (a,b,c,d) (a `RCons` b `RCons` c `RCons` d `RCons` RNil) where
   fromTuple (a,b,c,d) = a `RCons` b `RCons` c `RCons` d `RCons` RNil
   toTuple (a `RCons` b `RCons` c `RCons` d `RCons` RNil) = (a,b,c,d)

instance RTuple (a,b,c,d,e) (a `RCons` b `RCons` c `RCons` d `RCons` e `RCons` RNil) 
where
   fromTuple (a,b,c,d,e) = a `RCons` b `RCons` c `RCons` d `RCons` e `RCons` RNil
   toTuple (a `RCons` b `RCons` c `RCons` d `RCons` e `RCons` RNil) = (a,b,c,d,e)

instance RTuple (a,b,c,d,e,f) (a `RCons` b `RCons` c `RCons` d `RCons` e `RCons` f 
`RCons` RNil) where
   fromTuple (a,b,c,d,e,f) = a `RCons` b `RCons` c `RCons` d `RCons` e `RCons` f 
`RCons` RNil
   

RE: [Haskell] performance tuning Data.FiniteMap

2004-03-02 Thread MR K P SCHUPKE

I was thinking about improving array performance, and was wondering
if a transactional model would work well. You would keep a base copy
of the array, and any writes would be written to a delta style transaction
list. A reference to the array would be the list plus the base array.
Different references to the same array would just reference different
points in the delta list. The garbage colector would eat the delta list
from the tail, merging writes into the base array once references to
that part of the list are discarded. Writes would be very fast - just 
the time to add a delta to the transaction list. Reads would slow down
as the transaction list grows, but the list would only be as long as the
oldest reference, so providing references to very old copies of the
array are not required, the transaction list would remain short. It would
be even more efficient if the 'liveness' of references could be checked
when writing the array - at the cost of a slight slowdown in write 
performance.

I would be interested in any comments... I suspect somebody has done this
before, but I havent looked for any papers yet.

Regards
Keean Schupke.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Generics... no Tuples 2 either...

2004-03-02 Thread MR K P SCHUPKE
with reference to Ptr, I only need an instance of Data for the
Ptr () case (ie opaque pointers) ... so for generics it only needs
to know that a Ptr is a Ptr, and to treat it like a value.

Regards,
Keean Schupke.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Generics missing Data instances...

2004-02-26 Thread MR K P SCHUPKE

There appears to be no instance for Double values in the
Generics.Basic

Also no instance for Ptr.

am I not importing the right file, or does this need to be fixed?

Regards,
Keean Schupke.

PS. This is with ghc-6.2
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: ghc and signal processing

2004-02-23 Thread MR K P SCHUPKE
b - mapArray id a

The reason it is slow is because the array type is copied every time
a member is assigned.

There are two solutions:

1) Use a mutable-array in the StateMonad then freeze it.

2) In this particular case where processing is sequential (IE you
are only altering values based on *nearby* values, you can use streams.
One of the nicest features of Haskell is how lists (being lazy) operate
just like streams... 

So read the data into a list and define a filter of the type

filter :: [a] - [a]

Your program then becomes:

main :: IO ()
main = do
s - getMyDataAsList()
putMyList (filter s)

where the commands getMyDataAsList and putMyList have the types:

getMyDataAsList :: IO [a]

putMyList :: [a] - IO ()


This should be fast, and also use very little memory.

Regards,
Keean Schupke.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Array optimisation...

2004-02-23 Thread MR K P SCHUPKE

Was just thinking about GHC's implementation of arrays, and their 
poor performance. I know little about GHC's internal workings, but
I was thinking about how array performance could be improved.

What if when writing an array you instead construct a function:

f :: (Ix x,Ix y) = Array a - Ix x - a - Ix y - a
f a x b y | x==y = b
  | otherwise = a!y

Then the update in place operator // becomes a curried application
of 'f' above.

You could then define a a series of 'overlays' for a base array.
The clever bit would be to get the garbage collector to merge
the two as soon as any reference to the original array is
discarded.

Does GHC already do anything like this?

Regards,
Keean Schupke.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Subject: Generic compilation warnings...

2004-02-17 Thread MR K P SCHUPKE
When deriving Data with all warnings enabled, for example compiling the
following line:

data TestType = TestType Int deriving (Typeable,Data)

ghc 6.2 gives the following warnings:

Warning: Pattern match(es) are non-exhaustive
 In a case alternative:
 Patterns not matched: GHC.Base.I# #x with #x `notElem` [1#]

Is there a problem with the 'derived' code, or should this warning be
ignored?

regards,
Keean Schupke.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Subject: RE: Generics...

2004-02-09 Thread MR K P SCHUPKE
 the identity function will convert one to the other

Okay. This I understand.

I understand why the type of a generic transform has to be:

gtrans :: Data a = a - a

and thinking about this has given me the solution. Obviously 
my data types are wrong... If a loose one type and create an
angebraic type instead along the lines of:

data SqlType a = TypedExpr String | SqlColumn String

Then I can express the function I want generically. 
Where this leads to messy nested constructors, I can use
constructor functions to neaten things up again.

So... I need to think about the generic transforms I wish
to implement before specifying the data types. 

This will probably lead to a better use of the types anyway.

Regards,
Keean Schupke.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Generics...

2004-02-05 Thread MR K P SCHUPKE
 Presumably not replace all Ints by Floats

I've thought about it some more, and I don't think its
possible to do what I want using generics... Ideally I would like
to achieve the following type transformation:

type SqlColumn a = String
type TypedExpr a = Int

the function would map SqlColumns to TypedExpr... The actual code
generates an integer from a sequence to tag each column, but for
the sake of simplicity, the following types would be sufficient:

type SqlColumn a = String
type TypedExpr a = String

So we take a tuple of any length and return exactly the same
tuple, but with the types changed:

project :: (SqlColumn a,SqlColumn b) - (TypedExpr a,TypedExpr b)

project :: (SqlColumn a,SqlColumn b,SqlColumn c) - (TypedExpr a,TypedExpr b,TypedExpr 
c)


What do you think?

Regards,
Keean Schupke.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Generics and Substitution...

2004-02-04 Thread MR K P SCHUPKE

I have used generics in a couple of places (from the
scrap your boilerplate paper) and want to know if it is
possible to write a function that will (for example) change
the types 'in place' in a type. For example replace all the
elements in a tuple with a string (using Show):

(3 :: Int,3.5 :: Float,True :: Bool) - (3 :: String,3.5 :: String,True :: 
String)

Looking at the paper it seems a version of MkT with a different
type is required:

MkTT :: (Typeable a,Typeable b,Typeable c,Typeable d) = (c - d) - a - b

You could then use:

subInt :: Int - String
subInt i = showInt i 

again everywhere has the wrong type so something like:

everywhere' :: (Term a,Term b) = (forall c.Term c,forall d.Term d = c - d) - a - b
everywhere' f x = f (gmapTT (everywhere' f) x)

but can this gmapTT be defined in terms of gfoldl?

I tried to think about this... but I haven't quite got a handle
on gfoldl's type yet... Is it possible? Would the function look
like the definition of gmapT with a different type?

Regards,
Keean Schupke.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Generics...

2004-02-04 Thread MR K P SCHUPKE

I now have a vague clue how to do what I wanted. I wanted to substitute
types in place... a silly example would be to convert Ints to Floats and
Floats to Ints...

(3 :: Int, 4.0 :: Float) - (3.0 :: Float, 4 :: Int)

I already have a function that will convert the input to:

[(3,IntType),(4.0,FloatType)]

So I can then manipulate the list in this form to:  

[(3.0,FloatType),(4,IntType)]

All I now need to do is reconstruct back into the data structure...

I have however been unable to find any docs on gunfold which I 
think is the way to do this... 

If somebody point me to some documentation for gunfold, or
help in any way I would be very grateful...

Regards,
Keean Schupke.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Generics...(ish)

2004-01-28 Thread MR K P SCHUPKE
I have read the Scrap Your Boilerplate: A Practical Design
Pattern for Generic Programming and have worked out how to
do it. This seems much better than using Template Haskell for
this kind of problem. 

I used mkQ and extQ to convert from various types that are allowed
in the record structure, to an algebraic enumeration type that codes the
valid types. This allows using everything (++) to convert a record 
(tuple type) to a List of type-names in an enumeration. This is a very 
neet and compact way of doing it.

This enables me to define a database table in haskell (where a record 
represents a table with columns of the given types), for example:

data TestTable = TestTable {   
column1 :: ColumnType Int,
column2 :: ColumnType Float,
column3 :: ColumnType String
}

type ColumnType a = String -- use phantom types to statically type check sql...

testTable :: TestTable
testTable = TestTable {
column1 = id,
column2 = aFloatValue
column3 = aString
}

Using generics I can now generate a list:

[(id,SqlInt),(aFloatValue,SqlFloat),(aString,SqlString)]

which can be used to check the Haskell version of the table against the version
in the database, or create the table if none exists...

This is for a kind of port of the HaskellDB stuff to ghc, although it is more
of a complete reimplementation using the same idea. My aim is to use a monad
transformer, so that db operations can be interleaved with other IO.

Regards,
Keean Schupke.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Generics...(ish)

2004-01-21 Thread MR K P SCHUPKE

I am currently using template haskell to generate code to work on a 
record data type... This however is not very pretty, and I wondered if
there was another way to do what I want in GHC. I need to iterate over
the contents of a record for example:

data Test = Test { a :: Int, b :: String, c :: Float }

If I derive Typeable, I can compare the data-type, but not decompose it,
I don't know much about generics, and was wondering if I might be able to
do it that way...

The functionality I need is equivalent to being able to compare to instances,
for example, consider the type above, and the type below:

data Test2 = Test2 { x :: Int, y :: String, z :: Float, zz :: String }

i need to construct a function that could output the differenc between the
types, position at a time, so for the above the output would be:

Test2 contains extra String field.

or if y was to have the type Float,

Position 2 : Types differ (Test has String, Test2 has Float)
Test2 contains extra String field.


I could do this easily if Typeable was a concrete type just by using
case statements...

Regards,
Keean Schupke.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


GHC and UNICODE...

2003-12-19 Thread MR K P SCHUPKE

Whilst I appreciate the topic of show is not directly related to GHC,
what I would like to know is how to handle UNICODE properly... If I assume
I have a good unicode terminal, so stdin and stdout are in unicode format,
and all my text files are in unicode, how do I deal with this properly in
GHC... what is the current state of affairs?

Regards,
Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: DiffArray Performance

2003-11-06 Thread MR K P SCHUPKE
This is one good reason they have to be protected by MVars

Forgive my stupidity, but arn't the MVar operations (takeMVar, putMVar)
IO operation, therefore the locks must be in the IO monad, therefore
the code acting on the DiffArray should be in the IO monad... otherwise
they can't use the MVar calls? 

Regards,
Keean Schupke.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: DiffArray Performance

2003-11-05 Thread MR K P SCHUPKE
GHC only runs code on a single CPU at the moment

Is this true even if compiled with --threaded-rts ?

regards,
Keean Schupke.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: DiffArray Performance

2003-11-04 Thread MR K P SCHUPKE
never used in multi-threaded situation.

Erm, nearly all my code in Haskell is multi-threaded. One of the 
main reasons why I am using haskell is the low-cost light weight
multi-threading. Surely this is a big win for Haskell on SMP/Numa
machines - which are surely the future - as even Intel have realised
they can't just keep ramping up clock speeds and have gone multi-core
for their next pentium iteration. Just look at the benchmarks for the
multi-cpu opteron machines!

I would hesitate to make any type unsafe for multi-threading by default - I
think all the guards should be in as standard ... maybe a compile time
(or run-time) flag to replace the guards with NO-OPS for single CPU
machines might be a sensible option.

Regards,
Keean Schupke.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Template Haskell...

2003-10-31 Thread MR K P SCHUPKE

With reference to the future of template haskell - it would be nice if you could 
express the
following:

stringType :: String - Q [Dec]
stringType s = do
   x - gensym x
   y - gensym y
   return [
  Newtype [] s [] (Constr s [(Strict,Tcon (TconName String))]) [],
  Proto (show++s) (Tapp (Tapp (Tcon Arrow) (Tcon (TconName s))) (Tcon (TconName 
ShowS))),
  Fun (show++s) [Clause [Pcon s [Pvar x]]
 (Normal (App (Var showString) (Var x))) []],
  Instance [] (Tapp (Tcon (TconName Show)) (Tcon (TconName s))) [
 Fun showsPrec [Clause [Pwild,Pvar x]
(Normal (App (Var (show++s)) (Var x))) []]],
  Instance [] (Tapp (Tcon (TconName Eq)) (Tcon (TconName s))) [
 Fun == [Clause [Pcon s [Pvar x],Pcon s [Pvar y]]
(Normal (App (App (Var ==) (Var x)) (Var y))) []]] ]

AS

stringType :: String - Q [Dec]
stringType s = [|
newtype $s = $s String
show$s :: $s - ShowS
show$s ($s x) = showString x
instance Show $s where
showsPrec _ x = show$s x
instance Eq $s where
($s x) ($s y) = (x==y)
|]

Maybe with a more specific type like :

stringType :: TypeName - Q [Dec]

where TypeName would enforce the first letter must be capital rule.
NOTE: to work this would require show$s to crate a function name from
show prepended to the type name...

Why is this not possible with the current template-haskell, and would
this be possible with the proposed extensions (if not, why not, as the
above seems very easy to read?)

Regards,
Keead Schupke.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Template Haskell...

2003-10-30 Thread MR K P SCHUPKE

Just a thought, but once you have a data structure representing reified code
there is a couple of things it would be nice to be able to do:

1) use the Parser to read a source file (i'm assuming the parser produces the
same data stuctures as template haskell)

2) run the reified code directly (using ghci?) 



It looks from inspection that there is a Syntax.hs and a THSyntax.hs ... Is it 
possible to unify the data-types from these?

Can you use cmRunStmt to run a template instead of splicing it?

Regards,
Keean Schupke.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Templates...

2003-10-29 Thread MR K P SCHUPKE

I would like to create a template to generate type declarations, for example:

newtype mytype = myconstructor String

I am struggling without an example... how do I do it?

Regards,
Keean Schupke.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Template Haskell...

2003-10-29 Thread MR K P SCHUPKE

Okay, I have got my template working, but its extremely unreadable... could
anyone tell me how to make this look more like normal Haskell code?

stringType :: String - Q [Dec]
stringType s = do
   x - gensym x
   return [
  Newtype [] s [] (Constr s [(NonStrict,Tcon (TconName String))]) [],
  Proto (show++s) (Tapp (Tapp (Tcon Arrow) (Tcon (TconName s))) (Tcon (TconName 
ShowS))),
  Fun (show++s) [Clause [Pcon s [Pvar x]] (Normal (App (Var showString) (Var 
x))) []],
  Instance [] (Tapp (Tcon (TconName Show)) (Tcon (TconName s))) [
 Fun showsPrec [Clause [Pwild,Pvar x] (Normal (App (Var (show++s)) (Var 
x))) []]] ]
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC 6.2

2003-09-26 Thread MR K P SCHUPKE

Will the arrow's notation be in 6.2, whilst this is not vital, it would be very useful.

Regards,
Keean Schupke.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


my 2p's worth...

2003-09-19 Thread MR K P SCHUPKE

Would it not be better to have control over exactly where these options apply,
could you not have:

{-# OPTIONS fallow-overlapping-instances=true #-}

... some code ...

{-# OPTIONS -fallow-overlapping-instances=false #-}

... more code ...

So you can ensure instances you don't want overlapping cannot?

Regards,
Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Question regarding arrows...

2003-07-06 Thread MR K P SCHUPKE

I am trying to define the left operator for a CPS arrow of type:

newtype CPSFunctor ans a b c = CPS ((a c ans) - (a b ans))

This is the definition given by John Hughes for first:

first (CPS f) = CPS $ \k - arr (\(b,d) - (f (arr (\c - (c,d))  k),b))  app

So I try and apply this to left and get:

left (CPS f) = CPS $ \k - arr (\z - case z of
Left x - (f (arr Left  k),x)
Right x - (arr Right  k,x))  app

But when I compile (with ghc-6.0) I get:

Inferred type is less polymorphic than expected
Quantified type variable `d' is unified with another quantified type variable 
`b'
When trying to generalise the type inferred for `left'
Signature type: forall ans a.
(ArrowApply a, ArrowChoice a) =
forall b1 c1 d1.
CPSFunctor ans a b1 c1
- CPSFunctor ans a (Either b1 d1) (Either c1 d1)
Type to generalise: forall b1 c1 d1.
CPSFunctor ans a b1 c1
- CPSFunctor ans a (Either b1 d1) (Either c1 d1)
In the instance declaration for `ArrowChoice (CPSFunctor ans a)'

Hughes says in his paper that CPS arrows ... can of course support dynamic choice - 
so where am I going wrong with my definition? 

Any help greatly appreciated... 

Regards,
Keean Schupke.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: IO-System

2002-09-17 Thread MR K P SCHUPKE


I agree, I certainly don't want inefficency introduced by unecessary 
flushes, and
I would expect to control where the flushes happen. I think the query 
originally
assumed a sequencing ambiguity in the IO monad... but in my experiance 
(all be it
limited) the IO monad is there to ensure strict sequencing. To get the 
correct
results both buffers have to be changed...

module Main(main) where

import IO

main = do
   hSetBuffering stding NoBuffering
   hSetBuffering stdout NoBuffering
   echoTwice

echo = getChar = putChar
echoTwice = echo  echo


-- Or: using explicit flushing


module Main(main) where

import IO

main = do
hSetBuffering stdin NoBuffering
echoTwice
echo = getChar = putChar  hFlush stdout
echoTwice = echo  echo

Regards,
Keean Schupke.

Simon Marlow wrote:

I'd settle for that kind of indiscriminate flushing -- as is, 
trivial I/O examples such as

main = do
   putStr What is your name? 
   ls - getLine
   putStrLn (Hello  ++ ls ++ !)

fail to behave as expected.


That depends on what you expect... :-)  The Haskell report says nothing
about triggering a flush on stdout when reading from stdin.

I disagree that introducing this ad-hoc flush would be the right thing.
A workaround for a common misconception, yes; but not the right thing in
general.  IMHO, it's better that programmers learn about buffering early
because they'll get bitten by it later on anyhow.

Suppose we were to implement this, when exactly should it be enabled?
All the time?  When stdin is a terminal?  When stdin and stdout are both
connected to the same terminal?  For every output handle connected to
the same terminal as stdin?  Should it happen for a socket too?  (if
not, won't that be confusing for users?)

Cheers,
   Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users




___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



profiling objects (segmentation fault)

2002-07-15 Thread MR K P SCHUPKE

I know this has been discussed before, but I can't remember the 
conclusion and nothing seems to have
been done, so I am going to bring it up again.

Is there any way the compiler can mark object files with whether they 
are profiling or not, so that you cannot
link a profiled object with a non-profiled one. It seems quite bad that 
the program appears to compile and then
fails with a segmentation fault. Perhapse all profiling symbols could 
have prof appended - so they will not link
against non-profiling symbols of the same name?

Keean Schupke.


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



ghc and -fno-implicit-prelude

2002-07-09 Thread MR K P SCHUPKE

Can I get ghc to use a local definition of `=` and return... currently 
I have:

{-# OPTIONS -fglasgow-exts -fno-implicit-prelude #-}
module Main(main) where
import qualified Prelude (Monad(..))
import Prelude hiding (Monad(..))

... Then a definition of Monad using a Premonad for return, however when 
compiling
do notation it produces an error saying it cannot deduce (PrelBase.Monad p)

Can I force ghc to use the definition of the Monad class I have provided 
for do notation
(IE Monad derived from Premonad derived from Prelude.Functor)

Regards,
Keean.


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users