Re: Records in Haskell

2012-01-10 Thread Isaac Dupree

On 01/10/2012 05:06 AM, Greg Weber wrote:

Some of your comments seem to not fully recognize the name-spacing (plus
simple type resolution) aspect of this proposal that I probably didn't
explain well enough. Or maybe I don't understand your comments.

For record.field, field is under the record's namespace. A namespace (from
a module or under the new system a record), cannot export conflicting
names, and there this system prevents the importer from every having a
conflict with a record field name because the field is still under the
record's namespace when imported. The type system must resolve the type of
the record, and generally the field cannot contribute to this effort.


(I have only used Haskell for several years, not implemented Haskell 
several times; apologies for my amateurish understanding of the type 
system.)


So
Type inference proceeds assuming that "record.field" is something 
equivalent to "undefined record" (using "undefined" as a function type), 
and the program is only correct if the type of "record" resolves to a 
concrete type? I don't know if "concrete type" is at all the right 
terminology; I mean a type-variable doesn't count (whether 
class-constrained, "Num a => a", or not, "a", or even "m Int" is not 
concrete).  Is "forall a. Maybe a" okay (if Maybe were a record)? 
"forall a. Num a => Maybe a"?  I'm guessing "yes".

Does it get harder in the presence of the type-system extensions?
"(a ~ SomeRecord) => a": presumably that works with record syntax?  Can 
the compiler always figure out whether or not it can find a 
type-variable's concrete type?


My concept of Haskell is that (except for Template Haskell), scope 
resolution happens before type inference happens, no exceptions.  So 
you're deliberately breaking that pattern.  Right?


Does this order of stages (regular scope selection, then type inference, 
then record scope) make as high a fraction of code work as Frege's 
left-to-right model (which I am guessing interleaves type inference and 
record scope selection as it proceeds left-to-right through the program)?


Correct me if I got something wrong,

-Isaac

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


Re: Unit unboxed tuples

2012-01-10 Thread Tyson Whitehead
On January 10, 2012 12:18:13 wren ng thornton wrote:
> On 1/10/12 11:18 AM, Dan Doel wrote:
> > On Tue, Jan 10, 2012 at 11:14 AM, Dan Doel  wrote:
> >> On Tue, Jan 10, 2012 at 5:01 AM, Simon Marlow  wrote:
> >>> On 09/01/2012 04:46, wren ng thornton wrote:
>  Shouldn't (# T #) be identical to T?
> >>> 
> >>> No, because (# T #) is unlifted, whereas T is lifted.  In operational
> >>> terms, a function that returns (# T #) does not evaluate the T before
> >>> returning it, but a function returning T does.  This is used in GHC
> >>> for example to fetch a
> >>> 
> >>> value from an array without evaluating it, for example:
> >>>   indexArray :: Array# e ->  Int# ->  (# e #)
> 
> With my revised understanding we have the following family of types:
> 
>  T pointed,   lifted,   lazy
>  (# T #)   pointed?,  unlifted, lazy
>  !Tunpointed, lifted,   eager
>  {-#UNPACK#-}!Tunpointed, unlifted, eager
> 
> where the two !T types are only specified in ADTs and through strictness
> analysis. Though this doesn't explain the difference in operational
> behavior for their use as return types.

IIRC, don't functions in the STG machine evaluate their returned values to 
WHNF as the very fact that a (lazy) function has comes under valuation implies 
that its result is to be deconstructed (in a case statement)?

An unboxed tuple would already be in WHNF, so this would not be the case (it 
would be wrong to evaluate the arguments as the case statement forcing the 
valuation may not do more than deconstruct the unboxed tupple).

Cheers!  -Tyson

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


kinds for `*'

2012-01-10 Thread Serge D. Mechveliani
People,

GHC provides some extensions for kinds.
Does this make possible different kinds, for example, for `*' ?

Prelude.Num  has  * :: a -> a -> a.

And mathematicians also like to denote as `*' 
(\cdot in TeX)
a "multiplication of a vector v by a coefficient r". It is expressed by the 
declaration

  class (Num r, ...) => LeftModule r v where  * :: r -> v -> v

Regards,

--
Sergei
mech...@botik.ru

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


Re: Unit unboxed tuples

2012-01-10 Thread wren ng thornton

On 1/10/12 10:31 AM, Tyson Whitehead wrote:

On January 8, 2012 23:49:47 wren ng thornton wrote:

An alternative is to distinguish, say, (# x #) and its spaceful
constructor (# #) from the spaceless (##); and analogously for the boxed
tuples, though that introduces confusion about parentheses for boxing vs
parentheses for grouping.


I think that sounds pretty good.  Here is another that occured to me today

   (#), (# a #), (# a, b #), (# a, b, c #) ...

If you replace the internal ',' with '#'

   (#), (# a #), (# a # b #), (# a # b # c #), ...

you have number of elements = number of '#' - 1.


Yeah, I thought of suggesting (#) in lieu of (##). That might work 
better for parsing et alia since it removes the whitespace sensitivity 
of (##) vs (# #).


--
Live well,
~wren

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


Easiest way to extend CAS (casMutVar#) to boxed/unboxed Vector elements?

2012-01-10 Thread Ryan Newton
Hello there,

I was wondering what the recommendations would be for getting CAS on
[mutable] vector elements?

I thought that as a first step I might create an a library that does the
trick only for unboxed vectors, by using bits-atomic (i.e. FFI + GCC
intrinsics).

Roman Leshchinskiy recommended against depending on GCC.  He thought,
therefore, that not only boxed arrays but unboxed ones would need an extra
PrimOp to be handled properly:

> You can't rely on gcc extensions because code is usually compiled with the
> native code generator nowadays and doesn't go through gcc. The dependency
> on gcc will (hopefully) be dropped eventually anyway. So you'd probably
> also want primops for unboxed arrrays and Addr#.

Any advice?

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


Re: Unit unboxed tuples

2012-01-10 Thread wren ng thornton

On 1/10/12 11:18 AM, Dan Doel wrote:

On Tue, Jan 10, 2012 at 11:14 AM, Dan Doel  wrote:

On Tue, Jan 10, 2012 at 5:01 AM, Simon Marlow  wrote:

On 09/01/2012 04:46, wren ng thornton wrote:

Shouldn't (# T #) be identical to T?


No, because (# T #) is unlifted, whereas T is lifted.  In operational terms,
a function that returns (# T #) does not evaluate the T before returning it,
but a function returning T does.  This is used in GHC for example to fetch a
value from an array without evaluating it, for example:

  indexArray :: Array# e ->  Int# ->  (# e #)


I don't really understand this explanation. (# T #) being unlifted
would mean it's isomorphic to T under the correspondence e<->  (# e
#). _|_ = (# _|_ #) : (# T #), so this works.


With my revised understanding we have the following family of types:

T pointed,   lifted,   lazy
(# T #)   pointed?,  unlifted, lazy
!Tunpointed, lifted,   eager
{-#UNPACK#-}!Tunpointed, unlifted, eager

where the two !T types are only specified in ADTs and through strictness 
analysis. Though this doesn't explain the difference in operational 
behavior for their use as return types.


--
Live well,
~wren

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


Re: Unit unboxed tuples

2012-01-10 Thread Dan Doel
Copying the list, sorry. I have a lot of trouble replying correctly
with gmail's interface for some reason. :)

On Tue, Jan 10, 2012 at 11:14 AM, Dan Doel  wrote:
> On Tue, Jan 10, 2012 at 5:01 AM, Simon Marlow  wrote:
>> On 09/01/2012 04:46, wren ng thornton wrote:
>>> Shouldn't (# T #) be identical to T?
>>
>> No, because (# T #) is unlifted, whereas T is lifted.  In operational terms,
>> a function that returns (# T #) does not evaluate the T before returning it,
>> but a function returning T does.  This is used in GHC for example to fetch a
>> value from an array without evaluating it, for example:
>>
>>  indexArray :: Array# e -> Int# -> (# e #)

I don't really understand this explanation. (# T #) being unlifted
would mean it's isomorphic to T under the correspondence e <-> (# e
#). _|_ = (# _|_ #) : (# T #), so this works.

Does the difference have to do with unboxed types? For instance:

   foo :: () -> Int#
   foo _ = foo ()
   bar :: () -> (# Int# #)
   bar _ = (# foo () #)

   baz = case bar () of _ -> 5  -- 5
   quux = case foo () of _ -> 5 -- non-termination

Because in that case, either (# Int# #) is lifted, or the Int# is
effectively lifted when inside the unboxed tuple. The latter is a bit
of an oddity.

-- Dan

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


Re: Unit unboxed tuples

2012-01-10 Thread Tyson Whitehead
On January 8, 2012 23:49:47 wren ng thornton wrote:
> An alternative is to distinguish, say, (# x #) and its spaceful
> constructor (# #) from the spaceless (##); and analogously for the boxed
> tuples, though that introduces confusion about parentheses for boxing vs
> parentheses for grouping.

I think that sounds pretty good.  Here is another that occured to me today

  (#), (# a #), (# a, b #), (# a, b, c #) ...

If you replace the internal ',' with '#'

  (#), (# a #), (# a # b #), (# a # b # c #), ...

you have number of elements = number of '#' - 1.

Cheers!  -Tyson

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


Re: Unregistered builds broken?

2012-01-10 Thread Simon Marlow

On 10/01/2012 10:58, Joachim Breitner wrote:

Dear GHC team (esp. Simon and Ian),

thanks for fixing the exotic-architecture-build-errors in time for
7.4.1, everything compiles smoothly now:
https://buildd.debian.org/status/package.php?p=ghc&suite=experimental
(Well, arm* and mips* are not done yet, as they need more than one day,
but the others work so I am optimistic.)


That's good to hear, thanks for testing!

Simon


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


Re: More primops for integer arithmetic with overflow reporting

2012-01-10 Thread Ian Lynagh

Hi hvr,

On Tue, Jan 10, 2012 at 12:05:51PM +0100, Herbert Valerio Riedel wrote:
> 
> As the {Int,Word}{,8,16,32,64} types in Haskell are usually regarded to
> follow modulo arithmetic (w.r.t. to the Num-class ops), I was trying to
> implement efficient non-modulo Safe{Int,Word}{,8,16,32,64} types which
> would throw exceptions when the result falls outside the value domain
> representable.

Are you aware of http://hackage.haskell.org/package/safeint ?

> As ISAs often have hardware support to detect such overflows (e.g. on
> x86-64 via the OF/CF flags), I guess that by exploiting hardware
> support, this might allow for a reasonably efficient implementation of
> non-modulo integer arithmetic.

safeint doesn't do this yet, but it's part of the plan.

> So far I've only found 'addIntC#' and 'subIntC#' which perform the kind
> of operation I'm looking for. But this is only for signed integers, and
> as far as multiplication is concerned, there's a 'mulIntMayOflo#' but
> that may provide false negatives according to the documentation.
> 
> Therefore, I was wondering whether it'd make sense for GHC to provide
> more primops for the {Int,Word}{,8,16,32,64} types which return the
> result value together with an overflow-flag.

This is also relevant:
http://hackage.haskell.org/trac/ghc/ticket/5598


Thanks
Ian


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


More primops for integer arithmetic with overflow reporting

2012-01-10 Thread Herbert Valerio Riedel
Hello GHC HQ,

As the {Int,Word}{,8,16,32,64} types in Haskell are usually regarded to
follow modulo arithmetic (w.r.t. to the Num-class ops), I was trying to
implement efficient non-modulo Safe{Int,Word}{,8,16,32,64} types which
would throw exceptions when the result falls outside the value domain
representable.

As ISAs often have hardware support to detect such overflows (e.g. on
x86-64 via the OF/CF flags), I guess that by exploiting hardware
support, this might allow for a reasonably efficient implementation of
non-modulo integer arithmetic.

So far I've only found 'addIntC#' and 'subIntC#' which perform the kind
of operation I'm looking for. But this is only for signed integers, and
as far as multiplication is concerned, there's a 'mulIntMayOflo#' but
that may provide false negatives according to the documentation.

Therefore, I was wondering whether it'd make sense for GHC to provide
more primops for the {Int,Word}{,8,16,32,64} types which return the
result value together with an overflow-flag.

Thanks,
hvr



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


Re: Unregistered builds broken?

2012-01-10 Thread Joachim Breitner
Dear GHC team (esp. Simon and Ian),

thanks for fixing the exotic-architecture-build-errors in time for
7.4.1, everything compiles smoothly now:
https://buildd.debian.org/status/package.php?p=ghc&suite=experimental
(Well, arm* and mips* are not done yet, as they need more than one day,
but the others work so I am optimistic.)

Greetings,
Joachim


-- 
Joachim "nomeata" Breitner
Debian Developer
  nome...@debian.org | ICQ# 74513189 | GPG-Keyid: 4743206C
  JID: nome...@joachim-breitner.de | http://people.debian.org/~nomeata


signature.asc
Description: This is a digitally signed message part
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Records in Haskell

2012-01-10 Thread Greg Weber
Some of your comments seem to not fully recognize the name-spacing (plus
simple type resolution) aspect of this proposal that I probably didn't
explain well enough. Or maybe I don't understand your comments.

For record.field, field is under the record's namespace. A namespace (from
a module or under the new system a record), cannot export conflicting
names, and there this system prevents the importer from every having a
conflict with a record field name because the field is still under the
record's namespace when imported. The type system must resolve the type of
the record, and generally the field cannot contribute to this effort.

Otherwise the comments have some good ideas and details that I will have
time to look over in more detail and incorporate into the wiki later.

On Mon, Jan 9, 2012 at 6:07 PM, Greg Weber  wrote:

>
>
> On Mon, Jan 9, 2012 at 2:22 PM, Isaac Dupree <
> m...@isaac.cedarswampstudios.org> wrote:
>
>> You mean this wiki page, right?:
>> http://hackage.haskell.org/**trac/ghc/wiki/Records/**NameSpacing
>>
>>
>>  That is, there are no fundamental
>>> objections to the implementation of this records implementation.
>>>
>>
>> I think that might be overly optimistic... I think there's a risk that
>> SPJ finds an irritating complication to type inference & the rest of us
>> aren't type-system-savvy enough to continue trying to guess at that :) But
>> I think you're referring to whether we object to ad-hoc overloading of
>> record field names (neither parametric nor class-based polymorphism), if no
>> difficulties crop up.  Some of the concerns on http://www.haskell.org/**
>> haskellwiki/**TypeDirectedNameResolutionapply
>>  -- I'm not sure to what extent, but address those concerns rather
>> than require those people to repeat themselves again! :)
>>
>> (If we dodge all those obstacles, well, a better record system is better!)
>>
>>
> This shouldn't complicate type inference (other than the fact that we must
> avoid a left-right bias?) because the record field names are not overloaded
> - instead it puts some burden back on the user to add more type
> annotations. The difficult aspect of TDNR was that it was assuming
> overloading - although there is really no reason why it can't instead
> assume name-spacing. TDNR and this record proposal share many of the same
> syntax issues you list. Thanks for the detailed feedback! I am travelling
> right now, will review when I get a chance.
>
> Greg Weber
>
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Unit unboxed tuples

2012-01-10 Thread Simon Marlow

On 09/01/2012 04:46, wren ng thornton wrote:

On 12/23/11 8:34 AM, Simon Peyton-Jones wrote:

More uniform! If you the singleton-unboxed-tuple data constructor in
source code, as a function, you'd write (\x -> (# x #)). In a pattern,
or applied, you'd write (# x #).


Shouldn't (# T #) be identical to T?


No, because (# T #) is unlifted, whereas T is lifted.  In operational 
terms, a function that returns (# T #) does not evaluate the T before 
returning it, but a function returning T does.  This is used in GHC for 
example to fetch a value from an array without evaluating it, for example:


  indexArray :: Array# e -> Int# -> (# e #)

Cheers,
Simon



I know that a putative (T) would be different from T because it would
introduce an additional bottom, but I don't think that would apply to
the unboxed case. Or is there something in the semantics of unboxed
tuples that I'm missing?



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