[Haskell-cafe] Rank-2 polymorphism and overloading

2010-04-26 Thread Thomas van Noort

Hello all,

I'm having difficulties understanding rank-2 polymorphism in combination 
with overloading. Consider the following contrived definition:


f :: (forall a . Eq a = a - a - Bool) - Bool
f eq = eq True True

Then, we pass f both an overloaded function and a regular polymorphic 
function:


x :: forall a . Eq = a - a - Bool
x = \x y - x == y

y :: forall a . a - a - Bool
y = \x y - True

g :: (Bool, Bool)
g = (f x, f y)

Could someone explain to me, or point me to some reading material, why g 
is correctly typed?


I understand that x's type is what f expects, but why does y's 
polymorphic type fulfill the overloaded type of f's argument? I can 
imagine that it is justified since f's argument type is more restrictive 
than y's type. However, it requires y to throw away the provided 
dictionary under the hood, which seems counter intuitive to me.


Regards,
Thomas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Rank-2 polymorphism and overloading

2010-04-26 Thread Thomas van Noort

On 26-4-2010 20:13, Jochem Berndsen wrote:

Thomas van Noort wrote:

...


f requires a function that is able to compute, for two values of type a
(which instantiates Eq), a Boolean.

y certainly fulfills that requirement: it does not even require that the
values are of a type instantiating Eq.

This is also well-typed and might or might not be enlightening:


z :: forall a. Eq a =  a -  a -  Bool
z = y

g :: (Bool, Bool)
g = (f x, f z) -- note the use of z here instead of y


I find your example of z more intuitive as it is z that does not provide 
its dictionary to y, but throws it away explicitly. This in contrast to 
y that is provided a dictionary but throws it away implicitly.


Regards,
Thomas



Jochem


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Rank-2 polymorphism and overloading

2010-04-26 Thread Thomas van Noort

On 26-4-2010 20:12, Daniel Fischer wrote:

Am Montag 26 April 2010 19:52:23 schrieb Thomas van Noort:

...


Yes, y's type is more general than the type required by f, hence y is an
acceptable argument for f - even z :: forall a b. a -  b -  Bool is.


That's what I thought. I've just never seen such a notion of a more 
general type involving overloading before.





However, it requires y to throw away the provided
dictionary under the hood, which seems counter intuitive to me.


Why? y doesn't need the dictionary, so it just ignores it.


Sure, but y's type explicitly mentions that it doesn't want a 
dictionary, so why would you provide one to it?






Regards,
Thomas




Regards,
Thomas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type family signatures

2009-08-19 Thread Thomas van Noort

Thank your for this elaborate explanation, you made my day!

Thomas

Ryan Ingram wrote:

On Mon, Aug 17, 2009 at 12:12 AM, Thomas van Noorttho...@cs.ru.nl wrote:

Somehow I didn't receive David's mail, but his explanation makes a lot of
sense. I'm still wondering how this results in a type error involving rigid
type variables.


rigid type means the type has been specified by the programmer somehow.

Desugaring your code a bit, we get:

GADT :: forall a b. (b ~ Fam a) = a - b - GADT b

Notice that this is an existential type that partially hides a; all
we know about a after unwrapping this type is that (Fam a ~ b).

unwrap :: forall a b. (b ~ Fam a) = GADT b - (a,b)
unwrap (GADT x y) = (x,y)

So, the type signature of unwrap fixes a and b to be supplied by
the caller.  Then the pattern match on GADT needs a type variable for
the existential, so a new a1 is invented.  These are rigid because
they cannot be further refined by the typechecker; the typechecker
cannot unify them with other types, like a1 ~ Int, or a1 ~ a.

An example of a non-rigid variable occurs type-checking this expression:

foo x = x + (1 :: Int)

During type-checking/inference, there is a point where the type environment is:

(+) :: forall a. Num a = a - a - a

b :: *, non-rigid
x :: b

c :: *, non-rigid
foo :: b - c

Then (+) gets instantiated at Int and forces b and c to be Int.

In your case, during the typechecking of unwrap, we have:

unwrap :: forall a b. (b ~ Fam a) = GADT b - (a,b)
a :: *, rigid
b :: *, rigid
(b ~ Fam a)

-- From the pattern match on GADT:
a1 :: *, rigid
x :: a1
y :: b
(b ~ Fam a1)

Now the typechecker wants to unify a and a1, and it cannot,
because they are rigid.  If one of them was still open, we could unify
it with the other.

The type equalities give us (Fam a ~ Fam a1), but that does not give
us (a ~ a1).  If Fam was a data type or data family, we would know it
is injective and be able to derive (a ~ a1), but it is a type family,
so we are stuck.

  -- ryan


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type family signatures

2009-08-17 Thread Thomas van Noort
Somehow I didn't receive David's mail, but his explanation makes a lot 
of sense. I'm still wondering how this results in a type error involving 
rigid type variables.


Ryan Ingram wrote:

On Fri, Aug 14, 2009 at 12:03 PM, Dan Westonweston...@imageworks.com wrote:

But presumably he can use a data family instead of a type family to restore
injectivity, at the cost of adding an extra wrapped bottom value and one
more layer of value constructor?


Actually, you don't even necessarily pay this penalty, since you can
put newtypes into data families.


data family Foo a
newtype instance Foo () = UnitFoo Int


You do need to add the constructor wrap/unwrapping in code, but they
all get erased after typechecking.

  -- ryan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Type family signatures

2009-08-14 Thread Thomas van Noort

Hello,

I have a question regarding type family signatures. Consider the 
following type family:


  type family Fam a :: *

Then I define a GADT that takes such a value and wraps it:

  data GADT :: * - * where
GADT :: a - Fam a - GADT (Fam a)

and an accompanying unwrapper:

  unwrap :: GADT (Fam a) - (a, Fam a)
  unwrap (GADT x y) = (x, y)

When Fam is declared using the first notation,

  type family Fam a :: *

GHC HEAD gives the following error message:

  Main.hs:9:21:
Couldn't match expected type `a' against inferred type `a1'
  `a' is a rigid type variable bound by
  the type signature for `unwrap' at Main.hs:8:20
  `a1' is a rigid type variable bound by
   the constructor `GADT' at Main.hs:9:8
In the expression: x
In the expression: (x, y)
In the definition of `unwrap': unwrap (GADT x y) = (x, y)

However, when Fam is declared as (moving the a to the other side of the 
:: and changing it into *),


  type family Fam :: * - *

everything is ok. So, it seems to me that GHC HEAD considers both 
signatures to be really different. However, I do not quite understand 
the semantic difference in my example, other than that Fam needs to be 
fully satisfied in its named type arguments. Note that GHC 6.10.3 does 
not accept the latter signature for Fam since it requires at least one 
index for some reason, that's why I'm using GHC HEAD.


Regards,
Thomas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type constraints and classes

2009-04-26 Thread Thomas van Noort
This is a recurring problem[1] and I'm still looking for a really 
satisfying solution. The only working and non-verbose solution I found 
is the one Miguel suggests. Although I'm not too fond of splitting up 
the monadic functions into separate type classes. A similar solution is 
described elsewhere[2]. It also desribes how you can use Template 
Haskell to regain the power of the do-notation with your own restricted 
monad type class.


Kind regards,
Thomas

[1]
http://www.nabble.com/Monad-instance-for-Data.Set%2C-again-td16259448.html

[2]
http://www.randomhacks.net/articles/2007/03/15/data-set-monad-haskell-macros

Miguel Mitrofanov wrote:

{-# LANGUAGE MultiParamTypeClasses #-}
class Returnable m a where ret :: a - m a
class Bindable m a b where bind :: m a - (a - m b) - m b
newtype MOAMonad r m a = MOAMonad ((a - m r) - m r)
instance Monad (MOAMonad r m) where
return x = MOAMonad $ ($ x)
MOAMonad h = f = MOAMonad $ \p - h $ \x - let MOAMonad h' = f x 
in h' p

fromMOAMonad :: Returnable m r = MOAMonad r m r - m r
fromMOAMonad (MOAMonad h) = h ret
toMOAMonad :: Bindable m a r = m a - MOAMonad r m a
toMOAMonad mx = MOAMonad $ \p - bind mx p
class FMappable f a b where fmp :: (a - b) - f a - f b
newtype MOAFunctor r f a = MOAFunctor ((a - r) - f r)
instance Functor (MOAFunctor r f) where
fmap f (MOAFunctor h) = MOAFunctor $ \p - h $ p . f
fromMOAFunctor :: MOAFunctor r f r - f r
fromMOAFunctor (MOAFunctor h) = h id
toMOAFunctor :: FMappable f a r = f a - MOAFunctor r f a
toMOAFunctor fx = MOAFunctor $ \p - fmp p fx

-- MOA stands for Mother Of All

On 26 Apr 2009, at 15:21, Neil Brown wrote:


Hi,

I have a Haskell problem that keeps cropping up and I wondered if 
there was any solution/work-around/dirty-hack that could help.  I keep 
wanting to define class instances for things like Functor or Monad, 
but with restrictions on the inner type.  I'll explain with an 
example, because I find explaining this in words a bit difficult.  
Let's say I want to create a Monad instance for Set akin to that for 
lists:


==
import Data.Set
import Prelude hiding (map)

instance Monad Set where
return = singleton
m = f = fold union empty (map f m)

-- Error: Could not deduce (Ord a, Ord b) from the context (Monad Set)
==

Everything fits (I think) -- except the type-class constraints.  
Obviously my Monad instance won't work if you have things inside the 
set that aren't Ord, but I can't work out how to define a restricted 
instance that only exists for types that have Ord instances.  I can't 
express the constraint on the instance because the a and b types of 
return and = aren't visible in the class header.  Shifting the 
constraint to be present in the type doesn't seem to help either (e.g. 
newtype Ord a = MySet a = MySet (Set a)...).


Is there any way to get such instances as the one for Set working?  I 
cannot carry around a compare function myself in a data type that 
wraps Set, because return cannot create such functions without the 
original type-class instance.  I don't actually need a Monad for Set, 
but it neatly demonstrates my problem of wanting constraints on the 
type inside a Monad (or a Functor, or an Applicative, etc).


I worked around a similar problem with Functor by opting for a new 
Functor-like type-class with the constraints, but doing that with 
Monad rules out using all the monad helper functions (liftM, mapM, 
etc), and the do notation, which would be a step too far.  All 
suggestions are welcome, no matter how hacky, or how many GHC 
extensions are required :-) (provided they don't break all the other 
monads, e.g. redefining the signature of Monad).


Thanks,

Neil.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Overriding a Prelude function?

2009-04-22 Thread Thomas van Noort

You can hide () from the implicit import of Prelude using:

import Prelude hiding (())

Kind regards,
Thomas

michael rice wrote:
I've been working through this example from: 
http://en.wikibooks.org/wiki/Haskell/Understanding_monads


I understand what they're doing all the way up to the definition of 
(), which duplicates Prelude function (). To continue following the 
example, I need to know how to override the Prelude () with the () 
definition in my file rand.hs.


Michael

==

[mich...@localhost ~]$ cat rand.hs
import System.Random

type Seed = Int

randomNext :: Seed - Seed
randomNext rand = if newRand  0 then newRand else newRand + 2147483647
where newRand = 16807 * lo - 2836 * hi
  (hi,lo) = rand `divMod` 127773

toDieRoll :: Seed - Int
toDieRoll seed = (seed `mod` 6) + 1

rollDie :: Seed - (Int, Seed)
rollDie seed = ((seed `mod` 6) + 1, randomNext seed)

sumTwoDice :: Seed - (Int, Seed)
sumTwoDice seed0 =
  let (die1, seed1) = rollDie seed0
  (die2, seed2) = rollDie seed1
  in (die1 + die2, seed2)

() m n = \seed0 -
  let (result1, seed1) = m seed0
  (result2, seed2) = n seed1
  in (result2, seed2)

[mich...@localhost ~]$





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Performance question

2009-02-26 Thread Thomas van Noort

First thing I noticed, how about removing the sqrt in isInCircle:

isInCircle :: (Floating a, Ord a)  = (a,a) - Bool
isInCircle (x,y) = x*x + y*y = 1.0

But you can remove sqrt from the C++ implementation as well, so it only 
improves the relative performance if the C++ implementation of sqrt is 
worse than its Haskell counterpart.


Regards,
Thomas

hask...@kudling.de wrote:

Hi,

i have compared a C++ implementation with a Haskell implementation of the Monte 
Carlo Pi approximation:

http://lennart.kudling.de/haskellPi/

The Haskell version is 100 times slower and i wonder whether i do something 
obvious wrong.

Profiling says that the majority of the time is spend in main. But i have no 
idea where.

Can someone give me a hint?

Thanks,
Lenny

   individual
inherited
COST CENTRE  MODULE   
no.entries  %time %alloc   %time %alloc

MAIN MAIN   
1   0   0.00.0   100.0  100.0
 mainMain 
254   1  88.1   90.8   100.0  100.0
  monteCarloPi   Main 
255   1   0.61.111.99.2
   pairs Main 
2571000   0.71.4 0.71.4
   countHits Main 
2561001   4.22.910.66.7
accumulateHitMain 
25827852236   3.02.3 6.43.8
 isInCircle  Main 
2593000   3.31.5 3.31.5
 CAF:lit_r1A7Main 
248   1   0.00.0 0.00.0
  isInCircle Main 
260   0   0.00.0 0.00.0
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Performance question

2009-02-26 Thread Thomas van Noort
But you can remove sqrt from the C++ implementation as well, so it only 
improves the relative performance if the C++ implementation of sqrt is 
worse than its Haskell counterpart.


Oops, of course I mean, you only improve if Haskell's implementation is 
worse than C++'s implementation :)


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: rewriting-0.1

2008-11-13 Thread Thomas van Noort

Hi Greg,

We didn't look into nominal rewriting I'm afraid. And I'm not that
familiar with scrap-your-nameplate so I'm not sure if you can implement
nominal rewriting using that library.

Regards,
Thomas

Greg Meredith wrote:

Thomas,

Did you explore nominal rewrite at all? Do you know if it might be 
possible to use the scrap-your-nameplate package to implement some 
useful subset of the nominal rewrite machinery?


Best wishes,

--greg

--
L.G. Meredith
Managing Partner
Biosimilarity LLC
806 55th St NE
Seattle, WA 98105

+1 206.650.3740

http://biosimilarity.blogspot.com



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Proposal for associated type synonyms in Template Haskell

2008-11-12 Thread Thomas van Noort

Hi Pedro,

You are right, it is a partial implementation. We chose not to propose 
an implementation for associated datatypes and type families because it 
is unknown if there is a demand for it.


But I don't think coming up with the TH AST modifications for associated 
type synonyms and type families is that much harder. Especially 
associated datatypes are very similar to associated type synonyms. The 
difficult part is in the GHC translation of course.


Regards,
Thomas

José Pedro Magalhães wrote:

Hello Thomas,

I see this is a proposal for a partial implementation of #1673 
(http://hackage.haskell.org/trac/ghc/ticket/1673). Maybe it would be 
good if the remaining syntax (associated datatypes and type families) 
would also be defined and implemented in TH. Or maybe there isn't much 
demand for this?...



Cheers,
Pedro

On Wed, Nov 5, 2008 at 15:57, Thomas van Noort [EMAIL PROTECTED] 
mailto:[EMAIL PROTECTED] wrote:


Hello,

Recently, we released a library on Hackage for generic rewriting
(package rewriting if you are curious). The user of the library is
expected to define type class instances to enable rewriting on his
or her own datatypes. As these instances follow the datatype
declarations closely, we tried to generate the instances using
Template Haskell. Unfortunately, associated type synonyms are not
yet supported by TH.

After a presentation at the WGP'08, Simon encouraged us to write a
proposal about adding associated type synonyms to TH, so that it can
be added to GHC. So, here is our proposal.

The TH AST must allow 1) kind declarations of associated type synonyms
in class declarations and 2) their definitions in instance
declarations. For example,

class Foo a where
 type Bar a :: *

instance Foo Int where
 type Bar Int = String

The TH library defines a datatype Dec which contains a constructor
for class declarations and instance declarations:

data Dec
= ...
| ClassD Cxt Name [Name] [FunDep] [Dec]
| InstanceD Cxt Type [Dec]
 ...

1) Associated type synonym kind declarations

We suggest to add a constructor to the Dec type:

 ...
| AssocTySynKindD Name [Name] (Maybe Kind)
 ...

assocTySynKindD :: Name - [Name] - Maybe KindQ - DecQ

The first field is the name of the associated type synonym, the
second field is a list of type variables, and the third field is an
optional kind. Since kinds are not yet defined in TH, we have to add
some kind of kind definition (pun intended):

data Kind
= StarK
| ArrowK Kind Kind

type KindQ = Q Kind
starK :: KindQ
arrowK :: KindQ - KindQ - KindQ

We explicitly choose not to reuse the Type type to define kinds
(i.e., type Kind = Type as in GHC) since we think a separation
between the two worlds is much clearer to the users of TH.

2) Associated type synonym definitions

We suggest to add another constructor to the Dec type:

 ...
| AssocTySynD Name [Type] Type
 ...

assocTySynD :: Name - [TypeQ] - TypeQ - DecQ

The first field is the name of the type synonym, the second field is
a list of type arguments, and the third field is the body of the
type synonym.

We would like to hear your comments to this proposal.

Regards,
Thomas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org mailto:Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Proposal for associated type synonyms in Template Haskell

2008-11-05 Thread Thomas van Noort

Hello,

Recently, we released a library on Hackage for generic rewriting 
(package rewriting if you are curious). The user of the library is 
expected to define type class instances to enable rewriting on his or 
her own datatypes. As these instances follow the datatype declarations 
closely, we tried to generate the instances using Template Haskell. 
Unfortunately, associated type synonyms are not yet supported by TH.


After a presentation at the WGP'08, Simon encouraged us to write a 
proposal about adding associated type synonyms to TH, so that it can be 
added to GHC. So, here is our proposal.


The TH AST must allow 1) kind declarations of associated type synonyms
in class declarations and 2) their definitions in instance declarations. 
For example,


class Foo a where
  type Bar a :: *

instance Foo Int where
  type Bar Int = String

The TH library defines a datatype Dec which contains a constructor for 
class declarations and instance declarations:


data Dec
= ...
| ClassD Cxt Name [Name] [FunDep] [Dec]
| InstanceD Cxt Type [Dec]
  ...

1) Associated type synonym kind declarations

We suggest to add a constructor to the Dec type:

  ...
| AssocTySynKindD Name [Name] (Maybe Kind)
  ...

assocTySynKindD :: Name - [Name] - Maybe KindQ - DecQ

The first field is the name of the associated type synonym, the second 
field is a list of type variables, and the third field is an optional 
kind. Since kinds are not yet defined in TH, we have to add some kind of 
kind definition (pun intended):


data Kind
= StarK
| ArrowK Kind Kind

type KindQ = Q Kind
starK :: KindQ
arrowK :: KindQ - KindQ - KindQ

We explicitly choose not to reuse the Type type to define kinds (i.e., 
type Kind = Type as in GHC) since we think a separation between the two 
worlds is much clearer to the users of TH.


2) Associated type synonym definitions

We suggest to add another constructor to the Dec type:

  ...
| AssocTySynD Name [Type] Type
  ...

assocTySynD :: Name - [TypeQ] - TypeQ - DecQ

The first field is the name of the type synonym, the second field is a 
list of type arguments, and the third field is the body of the type synonym.


We would like to hear your comments to this proposal.

Regards,
Thomas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: rewriting-0.1

2008-10-22 Thread Thomas van Noort

Generic rewriting library for regular datatypes
===

This package provides rewriting functionality for regular datatypes.
Regular datatypes are recursive datatypes such as lists, binary trees,
etc. This library cannot be used with mutually recursive datatypes or
with nested datatypes.

This library has been described in the paper:

  A Lightweight Approach to Datatype-Generic Rewriting. Thomas van
  Noort, Alexey Rodriguez, Stefan Holdermans, Johan Jeuring, Bastiaan
  Heeren. ACM SIGPLAN Workshop on Generic Programming 2008.

More information about this library can be found at:

  http://www.cs.uu.nl/wiki/GenericProgramming/Rewriting

Features


* Generic rewriting machinery
* Generic traversals (top-down, bottom-up, etc.)
* Rewrite rules are defined concisely as values instead of functions,
  which allows for better observability
* Rewrite rules are defined in the original domain and do not require a
  manual extension for metavariables

Requirements


* GHC 6.10.1 (tested with 6.10.0.20081007)
* Cabal 1.2.1 (or higher)

Download  Source
-

Use cabal-install:

  cabal install rewriting

Get the package:

  http://hackage.haskell.org/cgi-bin/hackage-scripts/package/rewriting

Get the source:

  svn checkout https://svn.cs.uu.nl:12443/repos/dgp-haskell/rewriting

Bugs  Support
--

Report issues, request features, or just discuss the library with the
authors, maintainers, and other interested persons at:

  http://www.haskell.org/mailman/listinfo/generics
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Verifying a list of properties using QuickCheck

2008-10-20 Thread Thomas van Noort

Hi,

I would like to verify a list of properties using QuickCheck. Of course, 
I can test a single property using:


quickCheck :: Testable prop = prop - IO ()

Then, I can check a list of properties my mapping this function over a list:

quickCheckL :: Testable prop = [prop] - IO ()
quickCheckL = mapM_ quickCheck

This gives me a result for each property:

Prelude Test.QuickCheck quickCheckL [1==1,2==2]
OK, passed 100 tests.
OK, passed 100 tests.

However, I would like a single result for the complete list of 
properties instead of a result for each property. I realize that this 
restricts the properties to be of the same type, but that isn't a 
problem for my application.


Did I miss a library function that provides me this functionality?

Regards,
Thomas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] ANNOUNCE: Generic Haskell 1.80 (Emerald)

2008-04-22 Thread Thomas van Noort

Hello,

I took the liberty to move this discussion to the Haskell-Cafe mailing list.


Adrian Hey wrote:

Thomas van Noort wrote:

   Pleasant programming,


Hello,

This looks like good stuff. But having done all this work it seems
a pity not to go the extra mm and cabalise this and make it buildable
on all platforms (at least ghc supported platforms).


You are right, cabalizing the Makefiles implies that Generic Haskell can 
be build on any platform that is supported by GHC. However, this 
requires a tremendous amount of effort since the Makefiles of Generic 
Haskell are enormous.




The reason I'm interested is this may be useful for the GSoC project
I'm mentoring..

 http://code.google.com/soc/2008/haskell/about.html

But as things are, I'd be unlikely to consider introducing a dependency
on this. Even if it built out of the box with cygwin (which it
doesn't BTW) I don't really think many windows users will be keen to
install cygwin and learn how to use it just so they can build GH.


As you already noticed, there is no Windows binary available for the 
Emerald release. However, there is one for the Coral release, available 
from:


http://www.generic-haskell.org

Although this is an old release of Generic Haskell, this release already 
supports generic types, which is what you need for your project 
probably. In the user's guide, there is a small example available which 
defines a generic type to represent tries.


The latest release of Generic Haskell supports generic views for generic 
types. This allows you to define a generic type that generates efficient 
balanced tries, as you can read in my Master's thesis :) This requires 
the use of the balanced view on the type level. Unfortunately, this 
generic view is not implemented in the Generic Haskell compiler...




Thanks
--
Adrian Hey


Regards,
Thomas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: Generic Haskell 1.80 (Emerald)

2008-04-14 Thread Thomas van Noort

Pablo Nogueira wrote:

This has certainly been taken into account when comparing approaches to
 generic programming. I quote from page 18/19 from the work you and Bulat


Indeed I was not aware of it. Missed that. Thanks for pointing it out!


 Thus, full reflexivity of an approach is taken into account. This suggests
 constrained types are part of Haskell98. So, I'm a bit confused at the
 moment as well.


After reading the Haskell 98 report more carefully I think constrained
types are part of Haskell98. The syntax for algebraic datatype
declarations given is:

  data cx = T u1 ... uk = K1 t11 ... t1k1 | ...| Kn tn1 ... tnkn

Certainly, they are implemented in a peculiar way, with constraints
associated with value constructors and not the type, perhaps to keep
the class and kinds orthogonal (eg, the BinTree type has * - * kind
instead of Ord - * kind).


You are completely right, constraints are optional for data and newtype 
declarations in Haskell98:


http://www.haskell.org/onlinereport/syntax-iso.html#sect9.5

In addition, GHC supports liberalised type synonyms which allows you to 
define constraints:


http://www.haskell.org/ghc/docs/latest/html/users_guide/data-type-extensions.html#type-synonyms

Seems like the mystery is solved now..



At any rate, this has been discussed before in other threads.
Thanks Thomas for your help
P.


You're welcome,
Thomas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: Generic Haskell 1.80 (Emerald)

2008-04-12 Thread Thomas van Noort
 Generic Haskell version 1.80 (Emerald)
 ==

We are happy to announce the fifth release of Generic Haskell,
an extension of Haskell that facilitates generic programming.

Generic Haskell includes the following features:

* type-indexed values -- generic functions that can be
   instantiated on all Haskell data types.

* type-indexed types -- types which are indexed over the type
   constructors underlying Haskell datatypes.

The Generic Haskell compiler takes Generic Haskell source
and produces Haskell code.


Changes since 1.62 (Diamond)


* Generic views for generic types [1] are now supported.

* The implementation of type-indexed types is improved.


Download


The Generic Haskell compiler is available in source and binary
distributions. Binaries for Linux, Windows, and MacOSX
are available. These are available from:

 http://www.generic-haskell.org/compiler.html

The documentation is also available separately from that page.

For more general information, point your browser to:

 http://www.generic-haskell.org


Why Generic Haskell?


Software development often consists of designing datatypes, around which
functionality is added.  Some functionality is datatype
specific, whereas other functionality is defined on almost all
datatypes in such a way that it depends only on the structure of the
datatype.  A function that works on many datatypes in this way
is called a generic function.  Examples of generic functionality
include editing, pretty-printing or storing a value in a database, and
comparing two values for equality.

Since datatypes often change and new datatypes are introduced, we
have developed Generic Haskell, an extension of the functional
programming language Haskell that supports generic definitions,
to save the programmer from (re)writing instances of generic
functions. The original design of Generic Haskell is based on work by Ralf
Hinze.

   Pleasant programming,
   The Generic Haskell Team at Utrecht University

   [EMAIL PROTECTED]

[1] Thomas van Noort. Generic views for generic types. Master's thesis,
Utrecht University, 2008.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: Generic Haskell 1.80 (Emerald)

2008-04-12 Thread Thomas van Noort
That's a good question. Unfortunately, only Haskell98 types are currently
supported by the Generic Haskell compiler.

But at first sight, implementing support for parametric types with class
constraints is not too hard. Class constraints of a parametric type need
to be propagated to its generated structure type.

Regards,
Thomas

 On 12/04/2008, Thomas van Noort [EMAIL PROTECTED] wrote:

  Generic Haskell includes the following features:

  * type-indexed values -- generic functions that can be
instantiated on all Haskell data types.
^^^

 I have perused the manual and wonder if parametric types with class
 constraints are now supported or are not considered Haskell types. I'm
 thinking of types such as

 data Ord a = BinTree a = Leaf | Node a (BinTree a) (BinTree a)
 data Functor f = GRose f a = GLeaf | GNode a (f(GTree f a))


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: Generic Haskell 1.80 (Emerald)

2008-04-12 Thread Thomas van Noort
 On 12/04/2008, Thomas van Noort [EMAIL PROTECTED] wrote:

 That's a good question. Unfortunately, only Haskell98 types are
 currently
  supported by the Generic Haskell compiler.

 I thought constrained types were Haskell 98, but now I'm in doubt...

I'm not 100% sure either, but according to the Haskell98 language report,
constrained types are not part of Haskell98,

http://haskell.org/onlinereport/basic.html ,

but are described as GHC language features,

http://www.haskell.org/ghc/docs/latest/html/users_guide/data-type-extensions.html


  But at first sight, implementing support for parametric types with
 class
  constraints is not too hard. Class constraints of a parametric type
 need
  to be propagated to its generated structure type.

 Certainly, but there are a few difficulties for higher-kinded types.
 An arguable solution: http://portal.acm.org/citation.cfm?id=1159868

 The reason I mention this is because Scrap your Boilerplate supports
 them whereas GH does not, and I'm not aware this has been taken into
 account when comparing these two approaches in the work cited by Bulat
 on this thread.


This has certainly been taken into account when comparing approaches to
generic programming. I quote from page 18/19 from the work you and Bulat
cited:

==
Full reflexivity. A generic programming language is fully reflexive if a
generic function can be used on any type that is definable in the
language. Generic Haskell is fully reflexive with respect to the types
that are definable in Haskell 98, except for constraints in data-type
definitions. So a data type of the form

data Eq a = Set a = NilSet | ConsSet a (Set a)

is not dealt with correctly. However, constrained data types are a corner
case in Haskell and can easily be simulated using other means.
Furthermore, Nogueira [69] shows how to make Generic Haskell work for data
types with constraints.
==

Thus, full reflexivity of an approach is taken into account. This suggests
constrained types are part of Haskell98. So, I'm a bit confused at the
moment as well.

Regards,
Thomas

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe