RE: GHC generated dll makes Excel crash on exit.

2007-12-03 Thread Simon Peyton-Jones
Better still, could you add a section to that page about DLLs and Excel? That'd 
be useful for others.

Simon

From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Olivier Boudry
Sent: 30 November 2007 18:09
To: glasgow-haskell-users@haskell.org
Subject: Re: GHC generated dll makes Excel crash on exit.

Sorry if I'm talking to myself, but I found a solution and thought it could be 
interesting for other people who need to call GHC created DLLs from Excel.

The solution is based on the information found in : 
http://haskell.org/haskellwiki/GHC/Using_the_FFI#Debugging_Haskell_DLLs.

As suggested, I added two extra functions in my dllMain.c file (adder_Begin, 
adder_End) and removed the startupHaskell call from the dllMain function.

adder_Begin contains the startupHaskell call and adder_End the shutdownHaskell. 
dllMain just returns true. I also adapted the Excel VBA code to call 
adder_Begin on a WorkBook_Open event and adder_End on a WorkBook_BeforeClose 
event.

The VBA looks like this:

Public functions in a new Module1 module (cannot declare Public functions in 
the ThisWorkbook module):
Public Declare Function adder Lib  adder.dll Alias [EMAIL PROTECTED] (ByVal 
x As Long, ByVal y As Long) As Long
Public Declare Function adder_Begin Lib adder.dll () As Boolean
Public Declare Sub adder_End Lib adder.dll ()

Private functions the the ThisWorkbook module:
Private Sub Workbook_BeforeClose(Cancel As Boolean)
adder_End
End Sub

Private Sub Workbook_Open()
adder_Begin
End Sub

The GHC dllMain.c looks like this:
#include windows.h
#include Rts.h

#define __ADDER_DLL_EXPORT
#define ADDER_API _declspec(dllexport)

extern void __stginit_Adder(void);

static char* args[] = { ghcDll, NULL };
/* N.B. argv arrays must end with NULL */

BOOL STDCALL DllMain( HANDLE hModule,
   DWORD  ul_reason_for_call,
   LPVOID lpReserved
  ){
  return TRUE;
}

ADDER_API BOOL adder_Begin(){
  startupHaskell(1, args, __stginit_Adder);
  return HS_BOOL_TRUE;
}

ADDER_API void adder_End(){
  shutdownHaskell();
}

If somebody wants the code and Excel file, just ask, I'll be happy to provide 
it.

Thanks,

Olivier.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: win32ghc: using more than 2gb of memory

2007-12-03 Thread Simon Peyton-Jones
GHC definitely does not assume that the top bit is of an address is clear. But 
I don't know that anyone has explicitly tested it on a 3Gb program.

Simon

| -Original Message-
| From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of
| Bulat Ziganshin
| Sent: 02 December 2007 14:12
| To: glasgow-haskell-users@haskell.org
| Subject: win32ghc: using more than 2gb of memory
|
| Hello
|
| is it possible to use more than 2gb of memory for win32 ghc-compiled
| programs? does anyone checked this? i've found that the following
| switch should be added to cmdline:
|
| ghc ...  -optl --large-address-aware
|
| but can't check compiled executable
|
| if this question was never considered, here is some possible problems
| which may arise:
| http://blogs.msdn.com/oldnewthing/archive/2004/08/12/213468.aspx
|
| --
| Best regards,
|  Bulat  mailto:[EMAIL PROTECTED]
|
| ___
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users@haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: fundeps help

2007-12-03 Thread Simon Peyton-Jones
| I'm trying to understand what fundeps do and don't let me do. One
| particular source of confusion is why the following program doesn't
| typecheck:
|
| {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
| module Fundeps where
|
| class Dep a b | a - b, b - a
|
| conv :: (Dep a b1,Dep a b2) = b1 - b2
| conv = id
| {- end of program -}

GHC implements improvement by *identifying* the two equal types.  Here they 
cannot be identified because they are separate type variables.  A good way to 
think of this is to imagine translating the program into System F: you can't do 
it.  Functional dependencies guide type inference by adding extra unifications, 
resolving types that would otherwise be under-constrained and ambiguous -- but 
fundeps (or at least GHC's implementation thereof) does not deal with the case 
where the types become *over*-constrained.

GHC's new intermediate language, System FC, is specifically designed to do 
this.  Currently we're in transition: equality constraints are starting to 
work, but fundeps are implemented as they always were.  I hope we can 
eventually switch over to implementing fundeps using equality constraints, and 
then the above program will work.

Meanwhile, in the HEAD you can write
conv :: (a~b) = a - b
conv = id

Which, IHMO, is a much clearer way to say it!

You may also like to try the paper that Martin and I and others wrote about 
fundeps:
http://research.microsoft.com/%7Esimonpj/papers/fd-chr

Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC porting to FreeBSD-amd64 progress report

2007-12-03 Thread Simon Marlow

Wilhelm B. Kloke wrote:

Simon Marlow [EMAIL PROTECTED] schrieb:

Perhaps you compiled mkDerivedConstants as a 32-bit executable?


Yes. I was not attentive enough.

But now I have got a working compiler on FreeBSD-amd64-7.0. If anybody is
interested, I shall prepare a package of the installed binaries.


If you can build a binary distribution, we'll happily upload it to 
haskell.org and make it available for download.  Just 'make binary-dist' 
should produce a suitable distribution.


However, you might want to wait for 6.8.2 in the next few days, as we fixed 
several important bugs.



The compiler is good enough to compile itself now. Though there are
problems remaining. One the programs I tested the computation of
Meertens numbers from Bird/Wadler's book. This program segfaults on
amd64, but not on i386.


You'll probably find that the testsuite shows up this (and maybe other) 
bugs.  Start with a full testsuite run, is my advice.


Cheers,
Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: ghc vs ghci: why can't ghci do everything ghc can do?

2007-12-03 Thread Simon Marlow

Claus Reinke wrote:


3) suggestions:

   a) could we have a :make command in ghci that doesa 'ghc 
--make' while reusing the information fromthe current session?


Doesn't

  :set -fobject-code
  :reload

do that?


   b) could we have a --prefer-source option for ghci,
   so that 'ghc --make; ghci --prefer-source' will
   try to load all modules from source, but will fallback to 
the existing object files if necessary

   (instead of failing, as -fforce-recomp does)?
   c) allow selective switching between source and
   object files loaded into ghci (:prefer source M,N,..;
   :prefer object O,P,Q,..).


one important restriction (I'm not sure if you forgot this, but I'll point 
it out anyway), is that native-code modules can only depend on other 
native-code modules.  So falling back to native-code compilation might 
mean throwing away multiple modules already compiled to bytecode.  I don't 
like the sound of that - it would be better to put a flag in the module's 
OPTIONS pragma to indicate object code is required.


There are other proposals for specifying which modules get loaded as 
bytecode btw.  One is that the modules you name by filename get loaded as 
bytecode, the others get loaded as normal.  This seems the lightest 
solution to me, you would say


  :load M.hs N.hs


the application i have in mind is trying to use ghci on
non-trivial projects, such as darcs, or even ghc itself:

- it isn't possible to load all sources into ghci
- loading all object files is possible, but prevents
   use of ghci features such as ':m *Module',
   ':browse *Module', breakpoints, tags, ..
- ghci -fforce-recomp fails because it applies to allmodules
- there is substantial setup to do before one can
   call ghc or ghci, so dropping out of a sessionand trying to 
figure out dependencies and flags

   for compiling individual modules by hand isn't
   practical


  :set -fobject-code
  :load GHC.hs

(with the above extension)

Cheers,
Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Haddocumentation of 6.8.1

2007-12-03 Thread Daniel Fischer
Am Freitag, 30. November 2007 18:04 schrieb Wolfgang Jeltsch:
 Am Freitag, 30. November 2007 15:23 schrieb Daniel Fischer:
  Question 2: When I build a package via Cabal, is there a way to merge the
  documentation into the installed library docs (and if yes, how do I do
  it)?

 I think, if you do

 runhaskell Setup.[l]hs haddock

 before

 runhaskell Setup.[l]hs install

 then the latter installs the Haddock-generated API documentation and this
 documentation will be linked to by future Haddock-generated documentations
 when using Cabel to make them.

 Best wishes,
 Wolfgang

Yes, thanks, that's what cabal always did, I just thought it would be nice to 
have all installed libraries together because that would facilitate deciding 
whether I use something from the containers package, or the collections 
package or edison. But that's less important, really important is,

how do I get proper haddock docs built for my 6.8.x in the first place?
Currently, haddock doesn't find anything to link the docs for additional 
packages against. 

Thanks,
Daniel
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC porting to FreeBSD-amd64 progress report

2007-12-03 Thread Wilhelm B. Kloke
Simon Marlow [EMAIL PROTECTED] schrieb:
 Wilhelm B. Kloke wrote:
 
 However, you might want to wait for 6.8.2 in the next few days, as we fixed 
 several important bugs.

I have found a couple of small bugs regarding FreeBSD. Changing the 
configure process would be helpful.


FreeBSD-amd64 is identified as x86_64-unknown-freebsd, but the
entry in configure uses amd64-*-freebsd*r; this should be made consistent.
The FreeBSD cc needs -L/usr/local/lib and -I/usr/local/lib to
find the native gmp (and possibly others, too) library.

I tried to find out a way to use the FreeBSD-i386 ghc, which runs fine
on FreeBSD-amd64, for bootstrap. The problem in this case is to
substitute the 32bit assembler and linker instead of the 64bit versions.
In case of the assembler the script as32 was usable like this one:

#!/bin/sh
/usr/bin/cc -Xassembler -32 $*

But I failed to figure out the right ld32 script.
-- 
Dipl.-Math. Wilhelm Bernhard Kloke
Institut fuer Arbeitsphysiologie an der Universitaet Dortmund
Ardeystrasse 67, D-44139 Dortmund, Tel. 0231-1084-257
PGP: http://vestein.arb-phys.uni-dortmund.de/~wb/mypublic.key

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: fundeps help

2007-12-03 Thread Jan-Willem Maessen


On Dec 3, 2007, at 4:02 AM, Simon Peyton-Jones wrote:

GHC's new intermediate language, System FC, is specifically designed  
to do this.  Currently we're in transition: equality constraints are  
starting to work, but fundeps are implemented as they always were.   
I hope we can eventually switch over to implementing fundeps using  
equality constraints, and then the above program will work.


Meanwhile, in the HEAD you can write
   conv :: (a~b) = a - b
   conv = id

Which, IHMO, is a much clearer way to say it!


Is it really a good idea to permit a type signature to include  
equality constraints among unifiable types?  Does the above type  
signature mean something different from a -a?  Does the type signature:

foo :: (a~Bar b) = a - Bar b
mean something different from:
foo :: Bar b - Bar b
?  I know that System FC is designed to let us write stuff like:
foo :: (Bar a ~ Baz b) = Bar a - Baz b
Which is of course what we need for relating type functions.  But I'm  
wondering if there's a subtlety of using an equality constraint vs  
just substitution that I've missed---and if not why there are so many  
ways of writing the same type, many of them arguably unreadable!


Hoping this will give me a bit of insight into SystemFC,

-Jan-Willem Maessen

You may also like to try the paper that Martin and I and others  
wrote about fundeps:

   http://research.microsoft.com/%7Esimonpj/papers/fd-chr

Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: fundeps help

2007-12-03 Thread Simon Peyton-Jones

| Is it really a good idea to permit a type signature to include
| equality constraints among unifiable types?  Does the above type
| signature mean something different from a -a?  Does the type signature:
|  foo :: (a~Bar b) = a - Bar b
| mean something different from:
|  foo :: Bar b - Bar b
| ?  I know that System FC is designed to let us write stuff like:
|  foo :: (Bar a ~ Baz b) = Bar a - Baz b
| Which is of course what we need for relating type functions.  But I'm
| wondering if there's a subtlety of using an equality constraint vs
| just substitution that I've missed

No, you didn't miss anything.  I wouldn't expect anyone to write these types 
directly.  But it can happen:
class C a b | a-b
instance C Int Bool

class D x where
  op :: forall y. C x y = x - y

instance D Int where
  op = ...

In the (D Int) instance, what's the type of op?  Well, it must be
op :: forall y. C Int y = Int - y

And here we know that y=Bool; yet since we don't write the type sig directly we 
can't say it.  So GHC's implementation of fundeps rejects this program; again 
it can't be translated into System F.

Simon

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC generated dll makes Excel crash on exit.

2007-12-03 Thread Olivier Boudry
On 12/3/07, Simon Peyton-Jones [EMAIL PROTECTED] wrote:

  Better still, could you add a section to that page about DLLs and Excel?
 That'd be useful for others.



 Simon


Simon,

As the page is  part of the GHC documentation I cannot edit it. I put my
notes in a new wiki page :
http://haskell.org/haskellwiki/How_to_use_a_Haskell_Dll_from_Excel

I hope this is appropriate.

Best regards,

Olivier.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: GHC generated dll makes Excel crash on exit.

2007-12-03 Thread Simon Peyton-Jones
It's not part of the Haskell documentation!  The FFI page
http://haskell.org/haskellwiki/GHC/Using_the_FFI
is part of the contributed documentation, linked from here:
http://haskell.org/haskellwiki/GHC

So it absolutely is a Wiki, and should be editable by you (assuming you log 
into the wiki).

If not, let's see why not.  It'd be better to put your new material in with the 
other FFI stuff; it'll be easier to find that way.

THanks

SImon

From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Olivier Boudry
Sent: 03 December 2007 14:28
To: Simon Peyton-Jones
Cc: glasgow-haskell-users@haskell.org
Subject: Re: GHC generated dll makes Excel crash on exit.

On 12/3/07, Simon Peyton-Jones [EMAIL PROTECTED]mailto:[EMAIL PROTECTED] 
wrote:

Better still, could you add a section to that page about DLLs and Excel? That'd 
be useful for others.



Simon

Simon,

As the page is  part of the GHC documentation I cannot edit it. I put my notes 
in a new wiki page : 
http://haskell.org/haskellwiki/How_to_use_a_Haskell_Dll_from_Excel

I hope this is appropriate.

Best regards,

Olivier.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC generated dll makes Excel crash on exit.

2007-12-03 Thread Olivier Boudry
On Dec 3, 2007 10:07 AM, Simon Peyton-Jones [EMAIL PROTECTED] wrote:

  It's not part of the Haskell documentation!  The FFI page

 http://haskell.org/haskellwiki/GHC/Using_the_FFI

 is part of the contributed documentation, linked from here:

 http://haskell.org/haskellwiki/GHC



 So it absolutely is a Wiki, and should be editable by you (assuming you
 log into the wiki).



 If not, let's see why not.  It'd be better to put your new material in
 with the other FFI stuff; it'll be easier to find that way.



 THanks



 SImon


Simon,

I was talking about this page:
http://www.haskell.org/ghc/dist/current/docs/users_guide/win32-dlls.htmlwhich
is more Win32/Excel specific and is part of the GHC documentation.

But I agree it's easier to keep everything in one place so I will move my
stuff to the link you mentioned.

Best regards,

Olivier.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: HUnit 1.2.0.0 on 6.8.1 vs 1.1.1 on 6.6.1

2007-12-03 Thread Ian Lynagh
On Wed, Nov 21, 2007 at 11:13:26AM -0800, Greg Fitzgerald wrote:
 On Windows, HUnit's assertions are not working - trace below in ghci 6.8.1and
 6.6.1.  Can others reproduce?  Is this the right place to report bugs?
 Should I confirm a bug here and then create a ticket, create a ticket and
 that's it, or just mention it here and someone else creates a ticket?
 
 
 GHCi, version 6.8.1: http://www.haskell.org/ghc/  :? for help
 Loading package base ... linking ... done.
  :m Test.HUnit
  abc @=? efg
 Loading package HUnit-1.2.0.0 ... linking ... done.
 *** Exception: (unknown)
 
  / /_\// /_/ / /  | |  GHC Interactive, version 6.6.1, for Haskell 98.
 
  abc @=? efg
 Loading package HUnit-1.1.1 ... linking ... done.
 *** Exception: user error (HUnit:expected: abc
  but got: efg)

This is caused by a change in the HUnit library, from
assertFailure msg = ioError (userError (hunitPrefix ++ msg))
to
assertFailure msg = E.throwDyn (HUnitFailure msg)

We don't really have a good answer for where non-bootlib library bugs
should go at the moment. I don't know if Dean uses the sourceforge bug
tracker or not.


Thanks
Ian

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC generated dll makes Excel crash on exit.

2007-12-03 Thread Olivier Boudry
I moved my stuff to:
http://haskell.org/haskellwiki/GHC/Using_the_FFI#Beware_of_dllMain.28.29_-_Excel

Cheers,

Olivier.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Haddocumentation of 6.8.1

2007-12-03 Thread Wolfgang Jeltsch
Am Montag, 3. Dezember 2007 13:38 schrieben Sie:
 […]

 I just thought it would be nice to have all installed libraries together
 because that would facilitate deciding whether I use something from the
 containers package, or the collections package or edison.

Do you mean you want a combined contents page and a combined index?  Then have 
a look at libraries/gen_contents_index in the GHC 6.8.1 source tarball.  You 
might want to reuse this script.

 […]

Best wishes,
Wolfgang
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Type Families and enhanced constraints (at run-time)

2007-12-03 Thread Jim Burton
On Sat, 2007-12-01 at 11:33 +1000, Matthew Brecknell wrote:
[...]
 Seems impossible. With GADTs, you can of course go the other way:
 
  data A
  data B
  
  data Chr a where
AChr :: Chr A
BChr :: Chr B
  
  toChar :: Chr a - Char
  toChar AChr = 'A'
  toChar BChr = 'B'
 
 So perhaps insert should have a type something more like:
 
  type family ChrSetIns a t :: *
 
  insert :: Chr a - ChrSet t - ChrSet (ChrSetIns a t)
 
 I'm not sure how to make the set type parametric in the element type,
 though.
 

Thanks -- I think I see your point but I'm not sure how to make 
use of it...(perhaps I'm trying to run before I can walk). 
The way I was picturing things, the A, B ... types would 
need to take a parameter so they can be collected/consed, 
so my next attempt tries to incorporate both ideas:

data A
data B 
data Nil
data t ::: ts -- consing the phantom types

data Chr a where
AChr :: Chr A
BChr :: Chr B

toChar :: Chr a - Char
toChar AChr = 'A'
toChar BChr = 'B'

data TInfo t where
Nil  :: TInfo Nil
InsA :: TInfo t - TInfo (A ::: t)
InsB :: TInfo t - TInfo (B ::: t)

data ChrSet t = ChrSet (TInfo t) [Char]

type family ChrSetIns c s :: * 
type instance ChrSetIns (Chr a) (TInfo t) = TInfo (a ::: t)

insert :: Chr a - ChrSet t - ChrSet (ChrSetIns a t)
insert c (ChrSet tinfo cs) = case c of
AChr - ChrSet (InsA tinfo) ((toChar c):cs)
_   - error not a label

`insert' is still the problem -- how to form the 1st param 
of ChrSet. (InsA tinfo) isn't an instance of ChrSetIns, but 
I don't see how to fix that...? The error:
---
Couldn't match expected type `ChrSetIns A t'
   against inferred type `A ::: t'
  Expected type: TInfo (ChrSetIns A t)
  Inferred type: TInfo (A ::: t)
In the first argument of `ChrSet', namely `(InsA tinfo)'
In the expression: ChrSet (InsA tinfo) ((toChar c) : cs)
Failed, modules loaded: none.

Thanks,

Jim

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Type Families and enhanced constraints (at run-time)

2007-12-03 Thread Jim Burton
On Fri, 2007-11-30 at 13:37 +1100, Manuel M T Chakravarty wrote:
 Whenever you want to maintain type-level assertions of properties of  
 you functions, you need to decide *how much* of the value-level  
 information do you need on the type level to express and check the  
 properties that you are interested in.  

Hope you don't mind me going back to this point Manuel; given that I
want to maintain enough type-level information to provide correctness
checks on the implementations of set operations and on their inputs, is
this _impossible_ except at the extreme end of the spectrum? As you say
below, I was hoping this would not be the case and that it would be
possible to create something with those properties that could be used in
an interactive setting. Your SNat example is a simpler case, but it
pulls off that feat, which made me think it was a question of finding
the right combination of types.

Jim

 My SNat example was at one  
 extreme end of the spectrum: *complete* value-level information is  
 reflected at the type level.  In other case, it is only necessary to  
 reflect partial information; eg, when reasoning about bounds-checks of  
 bounded lists or arrays, only the length, but not the exact elements  
 need to be reflected.
 
 In other words, first you need to decide what properties you want to  
 enforce and what information you need to decide those properties.   
 Coming back to your set example, what properties do you want to  
 enforce/check and what information do you need to do that?  In the  
 extreme case, you could reflect the entire contents of each set at the  
 type-level using a singleton set type (and corresponding singleton  
 types for the set elements).  However, that also would mean that all  
 your value-level set operations will already have to be completely  
 executed by the type checker at compile time, which is probably not  
 what you want.
 
 Does this make sense?
 
 Manuel
 
 Jim Burton:
  Hi, I hope this is the right place to ask about working with type
  families...I want to make a library of Set operations that carries
  proofs at the type level, e.g. to make things like this possible,
 
  insert :: Member e s' T = e - Set s - Set s'
  union  :: Union s t u = Set s - Set t - Set u
 
  The trouble is designing the Set datatype so it can be used in type
  constraints *and* in run-time functionsSomething similar is of
  course possible with fun deps, and I knocked something up following  
  the
  example of Conrad Parker's 'Instant Insanity' but, crucially, that  
  code
  is 'trapped' in the type system with no populated types. I want
  term-level/run-time functions with enhanced constraints, such as in  
  the
  example Manuel posted in haskell-cafe:
 
  data Z
  data S a
 
  data SNat n where
 Zero :: SNat Z
 Succ :: SNat n - SNat (S n)
 
  zero = Zero
  one  = Succ zero
 
  type family (:+:) n m :: *
  type instance Z :+: m = m
  type instance (S n) :+: m = S (n :+: m)
 
  add :: SNat n - SNat m - SNat (n :+: m)
  add Zero m = m
  add (Succ n) m = Succ (add n m)
 
  This seems like the best of both worlds -- maybe it could be a  
  general
  strategy for making for making these enhanced constraints at the
  term-level? Make a (populated) GADT and parameterise it with a phantom
  type (perhaps amongst other things). Make a type operator that can be
  used to express the constraint on the phantom types carried around by
  the regular populated type. When the type operator appears in the
  codomain of the function it's a compile-time check on the  
  implementation
  of that function and when in the domain it checks the user at run- 
  time.
 
  However, (SNat n) can be put very succinctly because it doesn't need  
  to
  carry a value around other than the Peano number in the phantom type.
  What about Sets? In my case the values in the sets are just labels and
  could well be empty:
 
  data A ; data B ; data C
 
  And I also need to express the cons-ness -- I don't think that needs
  fancy constraints so it can be done with terms, e.g., an underlying
  sequence such as in the Collects example. Generally I need to work out
  what needs to be run-time and what compile-time but I think that would
  follow from getting the combinations of types and terms in the Set
  abstraction right...could someone give me a pointer with this?
 
  Many thanks,
 
  Jim
 
  ___
  Glasgow-haskell-users mailing list
  Glasgow-haskell-users@haskell.org
  http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: fundeps help

2007-12-03 Thread Ganesh Sittampalam

On Mon, 3 Dec 2007, Simon Peyton-Jones wrote:

No, you didn't miss anything.  I wouldn't expect anyone to write these 
types directly.  But it can happen:



   class C a b | a-b
   instance C Int Bool

   class D x where
 op :: forall y. C x y = x - y

   instance D Int where
 op = ...

In the (D Int) instance, what's the type of op?  Well, it must be
   op :: forall y. C Int y = Int - y

And here we know that y=Bool; yet since we don't write the type sig 
directly we can't say it.  So GHC's implementation of fundeps rejects 
this program; again it can't be translated into System F.


Conveniently, this is a good example of my other problem with fundeps :-) 
I can work around the problem from my first email with an unsafeCoerce, 
but is there any way I can get around the issue above at the moment in 
either 6.8 or the HEAD? I actually plan to recast the code in question 
using associated type synomyms once they're working properly, but would 
like to be able to make some progress now.


Cheers,

Ganesh
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Problems building and using ghc-6.9

2007-12-03 Thread Daniel Fischer
Hi,
so today I built ghc-6.9.20071124.

First, make died because HsColour version = 1.8 was needed, couldn't 
determine the version. I had HsColour 1.6, got myself 1.8, built and 
installed.
make died again, same problem.
I added (v, Version) to the optionTable in HsColour.hs and it worked :)

Then I tried to build zlib-0.4.0.1:
$ runghc ./Setup.hs configure --user --prefix=$HOME
Configuring zlib-0.4.0.1...
Setup.hs: At least the following dependencies are missing:
base =2.02.2
??? okay, there was something with flag bytestring-in-base, removed that, so 
that build-depends was base  2.0 || = 2.2, bytestring = 0.9, then
$ runghc ./Setup.hs configure --user --prefix=$HOME
Configuring zlib-0.4.0.1...
Setup.hs: At least the following dependencies are missing:
base 2.0||=2.2, bytestring =0.9

but:
$ ghc-pkg list
/home/dafis/lib/ghc-6.9.20071124/package.conf:
ALUT-2.1.0.0, Cabal-1.3, GLUT-2.1.1.1, HUnit-1.2.0.0,
OpenAL-1.3.1.1, OpenGL-2.2.1.1, QuickCheck-1.1.0.0, array-0.1,
base-3.0, bytestring-0.9, cgi-3001.1.5.1, containers-0.1,
directory-1.0, fgl-5.4.1.1, filepath-1.1, (ghc-6.9.20071124),
haskell-src-1.0.1.1, haskell98-1.0.1, hpc-0.5, html-1.0.1.1,
mtl-1.1.0.0, network-2.1.0.0, old-locale-1.0, old-time-1.0,
packedstring-0.1, parallel-1.0.0.0, parsec-2.1.0.0, pretty-1.0,
process-1.0, random-1.0, readline-1.0.1, regex-base-0.72.0.1,
regex-compat-0.71.0.1, regex-posix-0.72.0.2, rts-1.0, stm-2.1.1.0,
template-haskell-2.2, time-1.1.2.0, unix-2.2, xhtml-3000.0.2.1

and in stringsearch-0.2:
$ runghc ./Setup.lhs configure --user --prefix=$HOME
Configuring stringsearch-0.2...
Setup.lhs: At least the following dependencies are missing:
base -any

What's going on??

How can I build packages with ghc-6.9? 
Or do I have to go back to 6.8.1?

Thanks,
Daniel
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Type Families and enhanced constraints (at run-time)

2007-12-03 Thread Matthew Brecknell
Jim Burton said:
 Thanks -- I think I see your point but I'm not sure how to make 
 use of it...(perhaps I'm trying to run before I can walk). 
 The way I was picturing things, the A, B ... types would 
 need to take a parameter so they can be collected/consed, 
 so my next attempt tries to incorporate both ideas:
 
 [...]

I was imagining something more along the lines of this:

 data A
 data B
 
 data Chr a where
   AChr :: Chr A
   BChr :: Chr B
 
 toChar :: Chr a - Char
 toChar AChr = 'A'
 toChar BChr = 'B'
 
 data Nil
 data t ::: ts
 
 data ChrSet t where
   Nil :: ChrSet Nil
   Ins :: Chr a - ChrSet t - ChrSet (a ::: t)
 
 insert :: Chr a - ChrSet t - ChrSet (a ::: t)
 insert = Ins

That, by itself, doesn't require type families. I imagine you'll need
type families if you want to do things like implement a tree structure,
perform membership tests, deletions, etc.

Note that if you want to reason about the correctness of code in this
way, your data structures need to carry proofs. For example, the ChrSet
data type I've given above enforces the correspondence between the
value-level representation and the type-level representation, so given
any ChrSet, I know the type-level decomposition will reflect the
value-level decomposition, regardless of where that ChrSet came from.

On the other hand, the ChrSet you proposed in your previous post doesn't
have this property:

data ChrSet t = ChrSet (TInfo t) [Char]

Given one of these, I can't be confident that the type reflects the
value, without inspecting all of the code that might have contributed to
its construction. And that defeats the purpose of your endeavours. So
you should defer the call to toChar until the last possible moment, if
you call it at all.

Another thought occurred to me: you might want to construct a ChrSet
from user input, which brings us back to the problem I described in my
previous post. All is not lost, though. You'll just need to keep your
Chr and ChrSet values inside existential boxes:

 data ChrBox = forall a . ChrBox (Chr a)
 
 fromChar :: Char - ChrBox
 fromChar 'A' = ChrBox AChr
 fromChar 'B' = ChrBox BChr
 fromChar _ = error fromChar: bad Char
 
 data ChrSetBox = forall t . ChrSetBox (ChrSet t)
 
 insertChar :: Char - ChrSetBox - ChrSetBox
 insertChar c (ChrSetBox s) = case fromChar c of
   ChrBox c - ChrSetBox (insert c s)

BTW, I think you might get more interesting responses to theses
questions in haskell-cafe.

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: fundeps help

2007-12-03 Thread Manuel M T Chakravarty

Jan-Willem Maessen:
Is it really a good idea to permit a type signature to include  
equality constraints among unifiable types?  Does the above type  
signature mean something different from a -a?  Does the type  
signature:

   foo :: (a~Bar b) = a - Bar b
mean something different from:
   foo :: Bar b - Bar b
?  I know that System FC is designed to let us write stuff like:
   foo :: (Bar a ~ Baz b) = Bar a - Baz b
Which is of course what we need for relating type functions.  But  
I'm wondering if there's a subtlety of using an equality constraint  
vs just substitution that I've missed---and if not why there are so  
many ways of writing the same type, many of them arguably unreadable!


Simon answered most of your question, but let me make a remark  
regarding why there are so many ways of writing the same type, many  
of them arguably unreadable!  Equalities of the form a ~ someType  
are essentially a form of let-bindings for types - you can give a type  
a name and then use the name in place of the type.  Just like with  
value-level let bindings, you can abuse the notation and write  
unreadable terms.  However, this is no reason to remove let-bindings  
from the value level, so why should it be different at the type level?


Manuel

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users