Re: [Haskell-cafe] Re: distinguish functions from non-functions in a class/instances

2007-12-10 Thread Dan Weston

Questioning apfelmus definitely gives me pause, but...

 id :: a - a-- arity 1
   id = ($) :: (a - b) - (a - b)  -- arity 2

I agree with the arities given above (but without quotes) and see no 
ill-definedness to arity.


But these are two different classes of functions. There are arguments of 
the first function that cannot be applied to the second (e.g. 5). The 
fact that the two have different type signatures shows that Haskell can 
distinguish them (e.g. in the instantiation of a type class).


The difficulties of Haskell's type system in the presence/intersection 
of ad hoc/parametric polymorphism is an orthogonal issue. I think that 
every function application must have a unique monomorphic type at the 
call site of the arity function (assisted or not by type annotation), 
and this type is known to converge in a Template Haskell construction.


 We have to specialize the type of  id before
 supplying it to  wrap . For example,

   wrap (id :: Int - Int)

 works just fine.

The necessity of type annotation/restriction is an orthogonal issue to 
the above.


Am I missing something more fundamental?

apfelmus wrote:

Luke Palmer wrote:


Hmm, this still seems ill-defined to me.

compose :: (Int - Int - Int) - (Int - Int) - Int - Int - Int

Is a valid expression given that definition (with a,b = Int and c = 
Int - Int),

but now the arity is 4.


That's correct, the arity of a function is not well-defined due to 
polymorphism. The simplest example is probably


id :: a - a-- arity 1
  id = ($) :: (a - b) - (a - b)  -- arity 2

Therefore, the polymorphic expression

  wrap id

is problematic. It roughly has the type

  wrap id  ~~  [String] - a

But it's clearly ambiguous: do we have

  wrap id (x:_)   = read x

or

  wrap id (f:x:_) = wrap ($) (f:x:_) = read f (read x)

or what? (assuming a read instance for function types)
GHCi gives it a type

   :type wrap id
  wrap id :: (FunWrap (a - a) y) = [String] - y

but trying to use it like in

   let x = wrap id [1] :: Int

yields lots of type errors. We have to specialize the type of  id before 
supplying it to  wrap . For example,


  wrap (id :: Int - Int)

works just fine.


I don't like this behavior of  wrap  since it violates the nice property 
of polymorphic expressions that it's unimportant when a type variable is 
instantiated, like in


   map ((+1) :: Int - Int) [1..5]
 = map (+1) ([1..5] :: [Int])
 = (map (+1) [1..5]) :: [Int]



Regards,
apfelmus

___
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] Re: distinguish functions from non-functions in a class/instances

2007-12-10 Thread Jonathan Cast

On 10 Dec 2007, at 11:33 AM, Dan Weston wrote:


Questioning apfelmus definitely gives me pause, but...

 id :: a - a-- arity 1
   id = ($) :: (a - b) - (a - b)  -- arity 2

I agree with the arities given above (but without quotes) and see  
no ill-definedness to arity.


But these are two different classes of functions. There are  
arguments of the first function that cannot be applied to the  
second (e.g. 5). The fact that the two have different type  
signatures shows that Haskell can distinguish them (e.g. in the  
instantiation of a type class)


Not really.  The types of id and ($) can't be instances of a type  
class, since an instance of a type class has to be a monomorphic  
type.  So the decision as to which instance to use has to be made  
based on the particular monomorphic type id or ($) is used at.  But  
that monomorphic type may still contain free type variables; those  
type variables themselves represent some single monomorphic type,  
which may or may not be a function type.  So we still don't know what  
the arity of an arbitrary expression is.  (We don't know what its  
type is, even the way we know the type of id or ($), if it or any of  
its free variables is lambda-bound).


The difficulties of Haskell's type system in the presence/ 
intersection of ad hoc/parametric polymorphism is an orthogonal  
issue. I think that every function application must have a unique  
monomorphic type at the call site of the arity function (assisted  
or not by type annotation), and this type is known to converge in a  
Template Haskell construction.


 We have to specialize the type of  id before
 supplying it to  wrap . For example,

   wrap (id :: Int - Int)

 works just fine.

The necessity of type annotation/restriction is an orthogonal issue  
to the above.


Am I missing something more fundamental?

apfelmus wrote:

Luke Palmer wrote:


Hmm, this still seems ill-defined to me.

compose :: (Int - Int - Int) - (Int - Int) - Int - Int - Int

Is a valid expression given that definition (with a,b = Int and c  
= Int - Int),

but now the arity is 4.
That's correct, the arity of a function is not well-defined due to  
polymorphism. The simplest example is probably

id :: a - a-- arity 1
  id = ($) :: (a - b) - (a - b)  -- arity 2
Therefore, the polymorphic expression
  wrap id
is problematic. It roughly has the type
  wrap id  ~~  [String] - a
But it's clearly ambiguous: do we have
  wrap id (x:_)   = read x
or
  wrap id (f:x:_) = wrap ($) (f:x:_) = read f (read x)
or what? (assuming a read instance for function types)
GHCi gives it a type
   :type wrap id
  wrap id :: (FunWrap (a - a) y) = [String] - y
but trying to use it like in
   let x = wrap id [1] :: Int
yields lots of type errors. We have to specialize the type of  id  
before supplying it to  wrap . For example,

  wrap (id :: Int - Int)
works just fine.
I don't like this behavior of  wrap  since it violates the nice  
property of polymorphic expressions that it's unimportant when a  
type variable is instantiated, like in

   map ((+1) :: Int - Int) [1..5]
 = map (+1) ([1..5] :: [Int])
 = (map (+1) [1..5]) :: [Int]
Regards,
apfelmus
___
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] Re: distinguish functions from non-functions in a class/instances

2007-12-09 Thread Jonathan Cast

On 7 Dec 2007, at 12:39 PM, Dan Weston wrote:


Luke Palmer wrote:

On Dec 7, 2007 7:57 PM, Luke Palmer [EMAIL PROTECTED] wrote:

On Dec 7, 2007 7:41 PM, Dan Weston [EMAIL PROTECTED] wrote:

Luke Palmer wrote:

You can project the compile time numbers into runtime ones:
Yes, that works well if I know a priori what the arity of the  
function
is. But I want to be able to have the compiler deduce the arity  
of the
function (e.g. by applying undefined until it is no longer a  
function),

precisely so I don't have to supply it myself.

Function arity is (I think) something already known to GHC, so I  
don't

know why we can't get at it too.

No, it is not.  Consider:

compose f g x = f (g x)

What is the arity of f?

Oh, you're saying at run-time, given an object.


No, at compile time. Type is static.


What about a type that contains lexical type variables?

For that matter, what about a type that ends in a type variable, e.g.

head :: [a] - a

Is the arity of

head (x:xn) = x

Different from that of

head' :: [a - b] - a - b
head' (x:xn) = x

?

jcc

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


Re: [Haskell-cafe] Re: distinguish functions from non-functions in a class/instances

2007-12-07 Thread Luke Palmer
On Dec 7, 2007 6:27 AM, Victor Nazarov [EMAIL PROTECTED] wrote:
 Cool solution and not so complicated and ad-hoc. But I'd like to ask
 isn't the following definition is more natural and simple?

 nary 0 x [] = x
 nary n f (x:xs) | n  0 = nary (n-1) (f $ read x) xs

Sometimes it helps to write type signatures for functions.  As in this
case, where you'll find you won't be able to...  :-)

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


Re: [Haskell-cafe] Re: distinguish functions from non-functions in a class/instances

2007-12-07 Thread Victor Nazarov
On Dec 7, 2007 4:46 PM, Luke Palmer [EMAIL PROTECTED] wrote:
 On Dec 7, 2007 6:27 AM, Victor Nazarov [EMAIL PROTECTED] wrote:
 
  nary 0 x [] = x
  nary n f (x:xs) | n  0 = nary (n-1) (f $ read x) xs

 Sometimes it helps to write type signatures for functions.  As in this
 case, where you'll find you won't be able to...  :-)

 Luke


Ok :)

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

data Zero
data Succ a

class Nary n x y | n x - y where
  nary :: n - x - [String] - y

instance Nary Zero x x where
  nary _ x [] = x

instance (Nary n y z, Read x) = Nary (Succ n) (x-y) z where
  nary _ f (x:xs) = nary (undefined::n) (f $ read x) xs

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


Re: [Haskell-cafe] Re: distinguish functions from non-functions in a class/instances

2007-12-07 Thread Victor Nazarov
On Dec 7, 2007 2:52 PM,  [EMAIL PROTECTED] wrote:

 In fact, that distinction is possible. The following article

 How to write an instance for not-a-function
 http://okmij.org/ftp/Haskell/typecast.html#is-function-type

 specifically describes a method of writing an instance which is
 selected only when the type in question is NOT a function. The method
 is quite general and has been extensively used (for example, to
 implement deep monadic join).


Cool solution and not so complicated and ad-hoc. But I'd like to ask
isn't the following definition is more natural and simple?

nary 0 x [] = x
nary n f (x:xs) | n  0 = nary (n-1) (f $ read x) xs

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


Re: [Haskell-cafe] Re: distinguish functions from non-functions in a class/instances

2007-12-07 Thread Luke Palmer
On Dec 7, 2007 6:21 PM, Dan Weston [EMAIL PROTECTED] wrote:
 This is great! Two questions:

 1) I want to make sure the function arity matches the list length (as a
 runtime check). I think I can do this with an arity function using
 Data.Typeable. I came up with:

 arity f = a (typeOf f) where
a tr | typeRepTyCon tr /= mkTyCon - = 0
 | otherwise = 1 + (a . fromJust . funResultTy tr . head
  . typeRepArgs $ tr)

 This looks awful. Is there a better way to get the function arity?

 2) Once I have say arity (+) == 2 at runtime, how can I get it reified
 into Succ (Succ Zero)) at compile time to be able to use it as the first
 argument in your nary function? Can/should I use Template Haskell for this?

You can project the compile time numbers into runtime ones:

 class ProjectN n where
 projectN :: n - Int

 instance ProjectN Zero where
 projectN _ = 0

 instance (ProjectN n) = ProjectN (Succ n) where
 projectN _ = 1 + projectN (undefined :: n)

And then make sure the length matches the projected number of
arguments.  Other disagreements will be resolved at compile time.

Luke

 Dan

 Victor Nazarov wrote:
 
  {-# OPTIONS -fglasgow-exts #-}
  {-# OPTIONS -fallow-undecidable-instances #-}
 
  data Zero
  data Succ a
 
  class Nary n x y | n x - y where
nary :: n - x - [String] - y
 
  instance Nary Zero x x where
nary _ x [] = x
 
  instance (Nary n y z, Read x) = Nary (Succ n) (x-y) z where
nary _ f (x:xs) = nary (undefined::n) (f $ read x) xs
 



 ___
 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] Re: distinguish functions from non-functions in a class/instances

2007-12-07 Thread Dan Weston

This is great! Two questions:

1) I want to make sure the function arity matches the list length (as a 
runtime check). I think I can do this with an arity function using 
Data.Typeable. I came up with:


arity f = a (typeOf f) where
  a tr | typeRepTyCon tr /= mkTyCon - = 0
   | otherwise = 1 + (a . fromJust . funResultTy tr . head
. typeRepArgs $ tr)

This looks awful. Is there a better way to get the function arity?

2) Once I have say arity (+) == 2 at runtime, how can I get it reified 
into Succ (Succ Zero)) at compile time to be able to use it as the first 
argument in your nary function? Can/should I use Template Haskell for this?


Dan

Victor Nazarov wrote:



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


data Zero
data Succ a

class Nary n x y | n x - y where
  nary :: n - x - [String] - y

instance Nary Zero x x where
  nary _ x [] = x

instance (Nary n y z, Read x) = Nary (Succ n) (x-y) z where
  nary _ f (x:xs) = nary (undefined::n) (f $ read x) xs




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


Re: [Haskell-cafe] Re: distinguish functions from non-functions in a class/instances

2007-12-07 Thread Luke Palmer
On Dec 7, 2007 8:39 PM, Dan Weston [EMAIL PROTECTED] wrote:
  compose f g = f . g
 
  compose' f g x = f (g x)
 
  Are you saying that these two exactly equivalent functions should have
  different arity?   If not, then is the arity 2 or 3?

 Prelude :t let compose f g = f . g in compose
 let compose f g = f . g in compose :: (b - c) - (a - b) - a - c
 Prelude :t let compose' f g x = f (g x) in compose'
 let compose' f g x = f (g x) in compose' :: (t - t1) - (t2 - t) - t2
 - t1

 The arity is the number of top-level -

 Both are arity 3.


Hmm, this still seems ill-defined to me.

compose :: (Int - Int - Int) - (Int - Int) - Int - Int - Int

Is a valid expression given that definition (with a,b = Int and c = Int - Int),
but now the arity is 4.

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


Re: [Haskell-cafe] Re: distinguish functions from non-functions in a class/instances

2007-12-07 Thread Dan Weston

Luke Palmer wrote:

You can project the compile time numbers into runtime ones:


Yes, that works well if I know a priori what the arity of the function 
is. But I want to be able to have the compiler deduce the arity of the 
function (e.g. by applying undefined until it is no longer a function), 
precisely so I don't have to supply it myself.


Function arity is (I think) something already known to GHC, so I don't 
know why we can't get at it too.



On Dec 7, 2007 6:21 PM, Dan Weston [EMAIL PROTECTED] wrote:

This is great! Two questions:

1) I want to make sure the function arity matches the list length (as a
runtime check). I think I can do this with an arity function using
Data.Typeable. I came up with:

arity f = a (typeOf f) where
   a tr | typeRepTyCon tr /= mkTyCon - = 0
| otherwise = 1 + (a . fromJust . funResultTy tr . head
 . typeRepArgs $ tr)

This looks awful. Is there a better way to get the function arity?

2) Once I have say arity (+) == 2 at runtime, how can I get it reified
into Succ (Succ Zero)) at compile time to be able to use it as the first
argument in your nary function? Can/should I use Template Haskell for this?


You can project the compile time numbers into runtime ones:


class ProjectN n where
projectN :: n - Int

instance ProjectN Zero where
projectN _ = 0

instance (ProjectN n) = ProjectN (Succ n) where
projectN _ = 1 + projectN (undefined :: n)


And then make sure the length matches the projected number of
arguments.  Other disagreements will be resolved at compile time.

Luke


Dan

Victor Nazarov wrote:

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

data Zero
data Succ a

class Nary n x y | n x - y where
  nary :: n - x - [String] - y

instance Nary Zero x x where
  nary _ x [] = x

instance (Nary n y z, Read x) = Nary (Succ n) (x-y) z where
  nary _ f (x:xs) = nary (undefined::n) (f $ read x) xs




___
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] Re: distinguish functions from non-functions in a class/instances

2007-12-07 Thread Luke Palmer
On Dec 7, 2007 7:57 PM, Luke Palmer [EMAIL PROTECTED] wrote:
 On Dec 7, 2007 7:41 PM, Dan Weston [EMAIL PROTECTED] wrote:
  Luke Palmer wrote:
   You can project the compile time numbers into runtime ones:
 
  Yes, that works well if I know a priori what the arity of the function
  is. But I want to be able to have the compiler deduce the arity of the
  function (e.g. by applying undefined until it is no longer a function),
  precisely so I don't have to supply it myself.
 
  Function arity is (I think) something already known to GHC, so I don't
  know why we can't get at it too.

 No, it is not.  Consider:

 compose f g x = f (g x)

 What is the arity of f?

Oh, you're saying at run-time, given an object.

Still no, by some definition.

compose f g = f . g

compose' f g x = f (g x)

Are you saying that these two exactly equivalent functions should have
different arity?   If not, then is the arity 2 or 3?

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


Re: [Haskell-cafe] Re: distinguish functions from non-functions in a class/instances

2007-12-07 Thread Luke Palmer
On Dec 7, 2007 7:41 PM, Dan Weston [EMAIL PROTECTED] wrote:
 Luke Palmer wrote:
  You can project the compile time numbers into runtime ones:

 Yes, that works well if I know a priori what the arity of the function
 is. But I want to be able to have the compiler deduce the arity of the
 function (e.g. by applying undefined until it is no longer a function),
 precisely so I don't have to supply it myself.

 Function arity is (I think) something already known to GHC, so I don't
 know why we can't get at it too.

No, it is not.  Consider:

compose f g x = f (g x)

What is the arity of f?

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