Re: Anohter little question on using c2hs

2000-09-28 Thread Manuel M. T. Chakravarty

Jose Romildo Malaquias <[EMAIL PROTECTED]> wrote,

> I want to import some constants fromm a C header file
> that was defined as macros (using #define statements),
> with the c2hs program (latest from CVS).
> 
> The paper "C->Haskell, or Yet Another Interfacing Tool",
> by Manuel Chakravarty, tells me that it can be done
> with something like
> 
>   {#enum define ResultType { ERR as CursesError,
>, OK  as CursesOk
>}
>   #}
> 
> where the C header file has the macro definitions
> 
>   #define ERR (-1)
>   #define OK 0
> 
> But c2hs fails with the error message
> 
>   >>> Syntax error!
>   The phrase `ResultType' is not allowed here.
> 
> I have searched both c2hs and gtk+hs sources
> for an example using this feature of c2hs but
> failed to find one.

Yes, that is the only feature from the paper that isn't
implemented yet.  It is on the top of my todo list - as many
people want it.  Sorry for that.

Manuel




Re: negative export list

2000-09-28 Thread Marcin 'Qrczak' Kowalczyk

Thu, 28 Sep 2000 12:57:50 -0400, Zhanyong Wan <[EMAIL PROTECTED]> pisze:

> I guess the rational behind the current design is that everything
> by default should be private.

I guess that users of the module are interested in its interface,
i.e. what it exports. Enumeration of things that cannot be used is
not very helpful, even if it's shorter.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK





Re: Extensible data types?

2000-09-28 Thread Jose Romildo Malaquias

On Thu, Sep 28, 2000 at 12:00:11PM +0100, Chris Angus wrote:
> How about defining a Datatype Fn which defines all functions
> and building in terms of this
> 
> data Expr = Int Integer
>   | Cte String
>   | Var String
>   | App Fn [Expr] deriving (Show)
> 
> data Fn = Fn String
> | Combiner String
> | Compose Fn Fn deriving (Show)
> 
> class (Show a) => Fns a where
>  mkFn :: a -> Fn
>  mkFn x = Fn (show x)
> data Basic = Negate deriving (Show)
> data Combining = Sum | Prod deriving (Show)
> data Trig  = Sin | Cos | Tan deriving (Show)
> 
> instance Fns Trig
> instance Fns Basic
> instance Fns Combining where
>  mkFn x = Combiner (show x)
> 
> sine= mkFn Sin
> cosine  = mkFn Cos
> tangent = mkFn Tan
> neg  = mkFn Negate
> 
> compose :: Fn -> Fn -> Fn
> compose x y = Compose x y
> 
> match (Fn x) (Fn y) = x == y
> match (Combiner x) (Combiner y) = x == y
> match (Compose x y) (Compose a b) = match x a && ma
> match _ _ = False

Your solution should work, but the match operation, would be
too common in my system (it would be needed in order to
check the class of applications) and as it is based on
string (list of characters) equality, it would made the
system inefficient. If it was easy to keep this
structure, but obtain an unique integer (instead of
string) for each functor, this solution would be good enough
for me, as integer comparisons are much more efficient
than string comparison.

> diff :: Fn -> Fn
> diff fn | match fn sine   = cosine
> diff fn | match fn cosine = neg `compose` cosine

You forgot to differentiate the arguments of the function:

  data Diff = Diff deriving Show

  instance Fns Diff

  diffE :: Expr -> Expr -> Expr
  diffE (Int _) _ = Int 0
  diffE (Cte _) _ = Int 0
  diffE (Var x) (Var y)
 | x == y= Int 1
 | otherwise = Int 0
  diffE (App fn xs) (Var y) = App (diff fn) (map diffE xs)
  diffE x y = App Diff [x,y]

would be better (yeat too simplistic).

Romildo
-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil




type class

2000-09-28 Thread Zhanyong Wan

Hi,

In Haskell, instances of a type class can only be well-formed type
constructors, which in turn is defined by:

TC ::= T -- a type constant
 | a -- a variable
 | TC TC -- a type constructor application

Note there is no type constructor abstraction.

In practice, I found this rule too restrictive.  For example, given:

> data T a b = ...

T, T a and T a b are all valid candidates for instance declaration, but
T _ b is not (where _ is a hole waiting for a type parameter)!

Here is an example where I need an instance declaration for T _ b:

> data T a b = T (a -> b)
> 
> class Functor f where
>   fmap :: (x -> y) -> f x -> f y
> 
> class CoFunctor cf where
>   comap :: (x -> y) -> cf y -> cf x
> 
> instance Functor (T a) where
>   fmap f (T g) = T (f.g)

Now I want:

> instance CoFunctor (T _ b) where
>   comap f (T g) = T (g.f)

but this is invalid Haskell.

First I was attempted to write:

> type T' b a = T a b
> 
> instance CoFunctor (T' b) where ...

However, this is invalid too since a type synonym must be always fully
applied in Haskell.  (I guess this restriction is to ensure that a type
synonym always expands to a well-formed type constructor.)

Of course we can write:

> newtype T' b a = T' (T a b)
> 
> instance CoFunctor (T' b)

but this is not quite what I want: I am still unable to use T in the
context where class CoFunctor is required.

In retrospect, I realized even the _ notation I used is not expressive
enough: when there are more than one holes, we'd like to be able to
change their order.

How about extending TC with a branch for abstraction:

TC ::= ...
 | /\a. TC  -- abstraction

This is too powerful and will get out of control -- we surely don't want
to give TC the full power of lambda-calculus.  So let's impose a
restriction: in /\a.TC, a must occur free in TC *exactly once*.  This
way, abstraction can only be used to specify with respect to which
argument a partial application is.  (or I think so -- I haven't tried to
prove it.)

With the extension, we can have:

> instance CoFunctor (/\a. T a b) where ...

Why not extending Haskell to allow this?  Is it just that too few people
have asked for it?  Or is there any fundamental difficulty?  Or is the
problem not well studied yet?

-- Zhanyong Wan
Yale University




negative export list

2000-09-28 Thread Zhanyong Wan

Hello,

When writing a Haskell module, we can write

> module Foo ( x, y, z ) where

to express that x, y and z are the names we want to export.

This is nice as long as the export list is short.  However, often we
define a lot of stuff in a module and want *most* of them exported, and
we are cursed to write a long long export list.  What's more, whenever
an exported name is to be deleted from the module or the module is
extended with new functionalities, we have to remember to change the
export list accordingly.

Why not let Haskell support negative export list?  Like:

> module Foo hiding ( a, b, c ) where

My experience is that such negative export lists are usually much
shorter than the corresponding positive lists, and therefore much easier
to use.

I guess the rational behind the current design is that everything by
default should be private.  However, I doubt whether it is valid:  In
Haskell the let/where clause allows us to keep auxilliary functions from
polluting the top-level name space.  As a result, I seldom write
"private" functions at top-level, and I think the situation might be
true for other functional programmers as well.

-- Zhanyong Wan
Yale University




Anohter little question on using c2hs

2000-09-28 Thread Jose Romildo Malaquias

Hello.

I want to import some constants fromm a C header file
that was defined as macros (using #define statements),
with the c2hs program (latest from CVS).

The paper "C->Haskell, or Yet Another Interfacing Tool",
by Manuel Chakravarty, tells me that it can be done
with something like

  {#enum define ResultType { ERR as CursesError,
   , OK  as CursesOk
   }
  #}

where the C header file has the macro definitions

  #define ERR (-1)
  #define OK 0

But c2hs fails with the error message

  >>> Syntax error!
  The phrase `ResultType' is not allowed here.

I have searched both c2hs and gtk+hs sources
for an example using this feature of c2hs but
failed to find one.

Can someone please give me some light on this issue?

Romildo
-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil




RE: Extensible data types?

2000-09-28 Thread Chris Angus

How about defining a Datatype Fn which defines all functions
and building in terms of this

data Expr = Int Integer
  | Cte String
  | Var String
  | App Fn [Expr] deriving (Show)

data Fn = Fn String
| Combiner String
| Compose Fn Fn deriving (Show)

class (Show a) => Fns a where
 mkFn :: a -> Fn
 mkFn x = Fn (show x)
data Basic = Negate deriving (Show)
data Combining = Sum | Prod deriving (Show)
data Trig  = Sin | Cos | Tan deriving (Show)

instance Fns Trig
instance Fns Basic
instance Fns Combining where
 mkFn x = Combiner (show x)

sine= mkFn Sin
cosine  = mkFn Cos
tangent = mkFn Tan
neg  = mkFn Negate

compose :: Fn -> Fn -> Fn
compose x y = Compose x y

match (Fn x) (Fn y) = x == y
match (Combiner x) (Combiner y) = x == y
match (Compose x y) (Compose a b) = match x a && ma
match _ _ = False

diff :: Fn -> Fn
diff fn | match fn sine   = cosine
diff fn | match fn cosine = neg `compose` cosine




> -Original Message-
> From: Jose Romildo Malaquias [mailto:[EMAIL PROTECTED]]
> Sent: 25 September 2000 12:14
> To: Chris Angus
> Cc: [EMAIL PROTECTED]
> Subject: Re: Extensible data types?
> 
> 
> On Mon, Sep 25, 2000 at 11:37:24AM +0100, Chris Angus wrote:
> > I've not seen this before,
> > 
> > out of interest, why would you want/need such a thing?
> > > 
> > > Is there any Haskell implementation that supports
> > > extensible data types, in which new value constructors
> > > can be added to a previously declared data type,
> > > like
> > > 
> > >   data Fn = Sum | Pro | Pow
> > >   ...
> > >   extend data Fn = Sin | Cos | Tan
> > > 
> > > where first the Fn datatype had only three values,
> > > (Sum, Pro and Pow) but later it was extended with
> > > three new values (Sin, Cos and Tan)?
> 
> I want this to make a system I am workin on flexible.
> Without it, my system is going to be too rigid.
> 
> I am working on an Computer Algebra system to transform
> mathematic expressions, possibly simplifing them. There
> is a data type to represent the expressions:
> 
>   data Expr = Int Integer
>   | Cte String
>   | Var String
>   | App Fn [Expr]
> 
> An expression may be an integer, a named constante (to
> represent "known" contantes like pi and e), a variable
> or an application. An application has a functor (function
> name) and a list of arguments. The functor is introduced
> with
> 
>   data Fn = Sum | Pro | Pow
> 
> meaning the application may be a sum, a product or a
> power.
> 
> The project should be modular. So there are modules to
> deal with the basic arithmetic and algebraic transformations
> involving expressions of the type above. But there are
> optional modules to deal with trigonometric expressions,
> logarithms, vectors, matrices, derivatives, integrals,
> equation solving, and so on. These should be available as
> a library where the programmer will choose what he
> needs in his application, and he should be able to
> define new ones to extend the library. So these modules
> will certainly need to extend the bassic types above.
> 
> If it is really impossible (theoriticaly or not implemented)
> then I will have to try other ways to implement the idea.
> 
> The functions manipulating the expressions also should be
> extensible to accomodate new algorithms. The extensions
> is in a form of hooks (based on the Fn component of an
> application function) in the main algorithms.
> 
> Romildo
> -- 
> Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
> Departamento de Computação
> Universidade Federal de Ouro Preto
> Brasil
> 




Re: Extensible data types?

2000-09-28 Thread Peter Achten

At 12:55 26-9-00 -0300, Prof. José Romildo Malaquias wrote:

[...skip...]
This solution works great for the data type, but, at least
to me, it seems to make it too dificult to write functions
over ExprExt.

Consider for example the original version of the addition
operation (somehow simplified) on the original Expr data type

  data Fn = Sum | Pro | Pow

  data Expr = Int Integer | Cte String | Var String | App Fn
[Expr]

  add :: Expr -> Expr -> Expr
  add (Int x) (Int y) = Int (x + y)
  add (Int 0) x   = x
  add x   (Int 0) = x
  add x  
y   = App Sum [x,y]
[...skip...]

The problem with this function definition is that it, if you would
transform it using the scheme as I suggested earlier, returns results of
different types depending on the *value* of the first argument. You can
see this in the first two alternatives of add. If both arguments are of
type INT, then the result is of type INT. If the first argument has value
(INT 0) then the result has the same type as the second argument (which
can be CTE, VAR, or APP). Basically, it is the same problem as giving a
type to a function f which result type depends on its argument
value:

f 0 = "Zero"
f 1 = 1.0
f 2 = '2'

I don't think this can be solved readily in Haskell. It sounds as if you
need something like dynamic typing. I have added a reference [1] below
(for Clean; anybody out here with refs to dynamics in Haskell?). In any
case, that will not help you *right now*.

Finally, you remark:
The use of an existentialy quantified
variable
would solve this,

  data Expr
= 
Int Integer
   
| 
Cte String
   
| 
Var String
    |
forall a . (FnExt fn) => App fn Expr

but would make it to difficult to extend the
data type with new value constructors.
I am not sure if this will really help you. This will bring you back to
your initial problem: namely to extend constructors. In addition, the
solution also relies on the class member functions of FnExt.

Regards,
Peter

--
[1] Pil, M.R.C. (1999), Dynamic types and type
dependent functions, In Proc. of Implementation of
Functional Languages (IFL '98), London, U.K., Hammond, Davie and
Clack Eds., Springer-Verlag, Berlin, Lecture Notes in Computer Science
1595, pp 169-185.