reifying typeclasses (resend)

2013-09-15 Thread Evan Laforge
[ This is the second time I sent this, the first time it said it was
awaiting moderation because I'm not subscribed to haskell-cafe, which
is weird because I thought I was.  Did a bunch of people get
unsubscribed? ]

I'm sure this is old-hat to typeclass wizards, but I've managed to get
pretty far without understanding them too well, so here's a basic
question.  I haven't seen it phrased this way before though:

I have a typeclass which is instantiated across a closed set of 3
types.  It has an ad-hoc set of methods, and I'm not too happy with
them because being a typeclass forces them to all be defined in one
place, breaking modularity.  A sum type, of course, wouldn't have that
problem.  But in other places I want the type-safety that separate
types provide, and packing everything into a sum type would destroy
that.  So, expression problem-like, I guess.

It seems to me like I should be able to replace a typeclass with
arbitrary methods with just two, to reify the type and back.  This
seems to work when the typeclass dispatches on an argument, but not on
a return value.  E.g.:

{-# LANGUAGE ScopedTypeVariables #-}

class Taggable a where
toTagged :: a - Tagged
toTaggedType :: a - TaggedType
fromTagged :: Tagged - Maybe a

m_argument :: a - Int
m_result :: Int - a

data Tagged = TInt Int | TChar Char deriving (Show)
data TaggedType = TypeInt | TypeChar deriving (Show)

instance Taggable Int where
toTagged = TInt
toTaggedType _ = TypeInt
fromTagged (TInt x) = Just x
fromTagged _ = Nothing

m_argument = id
m_result = id

instance Taggable Char where
toTagged = TChar
toTaggedType _ = TypeChar
fromTagged (TChar x) = Just x
fromTagged _ = Nothing

m_argument = fromEnum
m_result = toEnum

argument :: (Taggable a) = a - Int
argument a = case toTagged a of
TInt x - x
TChar c - fromEnum c

result :: forall a. (Taggable a) = Int - a
result val = case toTaggedType (undefined :: a) of
TypeInt - val
TypeChar - toEnum val


Say m_argument and m_result are the ad-hoc methods I'd like to get out
of the typeclass.  I can do that well enough for 'argument', but
'result' runs into trouble.  One is the ugly undefined trick with
toTaggedType, but the bigger one is that ghc says 'Could not deduce (a
~ Int) from the context (Taggable a)'.  I wasn't really expecting it
to work, because it would entail a case with multiple types.  As far
as I know, the only way for that to happen is with GADTs.  But I don't
see how they could help me here.

So, perhaps my intuition was wrong.  toTagged and fromTagged methods
give you the power to go between value and type level, but apparently
that's not enough power to express what typeclasses give you.  Also it
seems like there's a fundamental difference between dispatching on
argument vs dispatching on result.

Is there a way to more formally understand the extents of what
typeclasses provide, and what a toTagged fromTagged scheme gives me,
so I can have a better intuition for how to go between value and type
levels?

Also, the toTaggedType thing is pretty ugly.  Not just passing it
undefined, but how it has to repeat the types.  I don't really see a
way to get around that though.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Recent problems with -cafe -- Fixed (I hope)

2013-09-15 Thread Gershom Bazerman

There were problems with the -cafe mailinglist today.

Best I can tell, we had an unplanned system reboot last night. In the 
course of it going down and back up, the configuration for -cafe got 
corrupted and the auto-fixed configuration had roughly 3/4 of the 
membership deleted.


I've gone in and replaced it with a recent backup config, which should 
have fixed the problem.


If this email goes through, then we're in good shape -- sorry about the 
mess.


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


Re: [Haskell-cafe] reifying typeclasses (resend)

2013-09-15 Thread Timon Gehr

On 09/15/2013 09:38 AM, Evan Laforge wrote:

...

It seems to me like I should be able to replace a typeclass with
arbitrary methods with just two, to reify the type and back.  This
seems to work when the typeclass dispatches on an argument, but not on
a return value.  E.g.:

...

Say m_argument and m_result are the ad-hoc methods  I'd like to get out
of the typeclass.  I can do that well enough for 'argument', but
'result' runs into trouble.  One is the ugly undefined trick with
toTaggedType, but the bigger one is that ghc says 'Could not deduce (a
~ Int) from the context (Taggable a)'.  I wasn't really expecting it
to work, because it would entail a case with multiple types.  As far
as I know, the only way for that to happen is with GADTs.  But I don't
see how they could help me here.



As follows:

{-# LANGUAGE GADTs, StandaloneDeriving #-}

class Taggable a where
toTagged :: a - Tagged a
toTaggedType :: TaggedType a
fromTagged :: Tagged b - Maybe a

data Tagged a where -- (example works if this is not a GADT)
  TInt  :: Int - Tagged Int
  TChar :: Char - Tagged Char

deriving instance Show (Tagged a)

data TaggedType a where
  TypeInt :: TaggedType Int
  TypeChar :: TaggedType Char

deriving instance Show (TaggedType a)

instance Taggable Int where
toTagged = TInt
toTaggedType = TypeInt
fromTagged (TInt x) = Just x
fromTagged _ = Nothing

instance Taggable Char where
toTagged = TChar
toTaggedType = TypeChar
fromTagged (TChar x) = Just x
fromTagged _ = Nothing

argument :: (Taggable a) = a - Int
argument a = case toTagged a of
TInt x - x
TChar c - fromEnum c

result :: (Taggable a) = Int - a
result val = go val $ toTaggedType
  where
go :: (Taggable a) = Int - TaggedType a - a
go val TypeInt = val
go val TypeChar = toEnum val



So, perhaps my intuition was wrong.  toTagged and fromTagged methods
give you the power to go between value and type level,  but apparently
that's not enough power to express what typeclasses give you.


You do get enough power to write that second function, but the result is 
necessarily uglier than if you use GADTs as there are less invariants 
expressed in the type system.


result :: (Taggable a) = Int - a
result val = case fromTagged (TInt val) of
  Just a - a
  Nothing - case fromTagged (TChar $ toEnum val) of
Just a - a
Nothing - case error matches are non-exhaustive of
  TInt _ - undefined
  TChar _ - undefined

(The last pattern match allows the compiler to warn you if 'result' gets 
out of sync with 'Tagged'.)



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


[Haskell-cafe] LATA 2014: 3rd call for papers

2013-09-15 Thread GRLMC
*To be removed from our mailing list, please respond to this message with
UNSUBSCRIBE in the subject line*


*

8th INTERNATIONAL CONFERENCE ON LANGUAGE AND AUTOMATA THEORY AND
APPLICATIONS

LATA 2014

Madrid, Spain

March 10-14, 2014

Organized by:

Research Group on Implementation of Language-Driven Software and
Applications (ILSA)
Complutense University of Madrid

Research Group on Mathematical Linguistics (GRLMC)
Rovira i Virgili University

http://grammars.grlmc.com/lata2014/

*


AIMS:

LATA is a yearly conference on theoretical computer science and its
applications. Following the tradition of the diverse PhD training events in
the field developed at Rovira i Virgili University in Tarragona since 2002,
LATA 2014 will reserve significant room for young scholars at the beginning
of their career. It will aim at attracting contributions from both classical
theory fields and application areas (bioinformatics, language technology,
artificial intelligence, etc.).

VENUE:

LATA 2014 will take place in Madrid, the capital of Spain. The venue will be
the School of Informatics of Complutense University.

SCOPE:

Topics of either theoretical or applied interest include, but are not
limited to:

algebraic language theory
algorithms for semi-structured data mining
algorithms on automata and words
automata and logic
automata for system analysis and programme verification
automata, concurrency and Petri nets
automatic structures
cellular automata
codes
combinatorics on words
compilers
computability
computational complexity
data and image compression
decidability issues on words and languages
descriptional complexity
DNA and other models of bio-inspired computing
digital libraries and document engineering
foundations of finite state technology
foundations of XML
fuzzy and rough languages
grammars (Chomsky hierarchy, contextual, unification, categorial, etc.)
grammatical inference and algorithmic learning
graphs and graph transformation
language varieties and semigroups
language-based cryptography
language-theoretic foundations of artificial intelligence and artificial
life
natural language and speech automatic processing
parallel and regulated rewriting
parsing
patterns
power series
quantum, chemical and optical computing
semantics
string and combinatorial issues in computational biology and bioinformatics
string processing algorithms
symbolic dynamics
symbolic neural networks
term rewriting
transducers
trees, tree languages and tree automata
weighted automata

STRUCTURE:

LATA 2014 will consist of:

invited talks
invited tutorials
peer-reviewed contributions

INVITED SPEAKERS:

Javier Esparza (Munich Tech, DE), On Trees and Fixed Point Equations
(tutorial)
Leslie A. Goldberg (Oxford, UK), The Complexity of Approximate Counting
Oscar H. Ibarra (Santa Barbara, US), tba
Sanjeev Khanna (Philadelphia, US), tba
Helmut Seidl (Munich Tech, DE), tba

PROGRAMME COMMITTEE:

Dana Angluin (Yale, US)
Eugene Asarin (Paris Diderot, FR)
Jos Baeten (Amsterdam, NL)
Christel Baier (Dresden, DE)
Jan Bergstra (Amsterdam, NL)
Jin-Yi Cai (Madison, US)
Marek Chrobak (Riverside, US)
Andrea Corradini (Pisa, IT)
Mariangiola Dezani (Turin, IT)
Ding-Zhu Du (Dallas, US)
Michael R. Fellows (Darwin, AU)
Jörg Flum (Freiburg, DE)
Nissim Francez (Technion, IL)
Jürgen Giesl (Aachen, DE)
Annegret Habel (Oldenburg, DE)
Kazuo Iwama (Kyoto, JP)
Sampath Kannan (Philadelphia, US)
Ming-Yang Kao (Northwestern, US)
Deepak Kapur (Albuquerque, US)
Joost-Pieter Katoen (Aachen, DE)
S. Rao Kosaraju (Johns Hopkins, US)
Evangelos Kranakis (Carleton, CA)
Gad M. Landau (Haifa, IL)
Andrzej Lingas (Lund, SE)
Jack Lutz (Iowa State, US)
Ian Mackie (École Polytechnique, FR)
Carlos Martín-Vide (Tarragona, ES, chair)
Giancarlo Mauri (Milan, IT)
Faron G. Moller (Swansea, UK)
Paliath Narendran (Albany, US)
Enno Ohlebusch (Ulm, DE)
Helmut Prodinger (Stellenbosch, ZA)
Jean-François Raskin (Brussels, BE)
Wolfgang Reisig (Humboldt Berlin, DE)
Marco Roveri (Bruno Kessler, Trento, IT)
Michaël Rusinowitch (LORIA, Nancy, FR)
Yasubumi Sakakibara (Keio, JP)
Davide Sangiorgi (Bologna, IT)
Colin Stirling (Edinburgh, UK)
Jianwen Su (Santa Barbara, US)
Jean-Pierre Talpin (IRISA, Rennes, FR)
Andrzej Tarlecki (Warsaw, PL)
Rick Thomas (Leicester, UK)
Sophie Tison (Lille, FR)
Rob van Glabbeek (NICTA, Sydney, AU)
Helmut Veith (Vienna Tech, AT)

ORGANIZING COMMITTEE:

Adrian Horia Dediu (Tarragona)
Ana Fernández-Pampillón (Madrid)
Carlos Martín-Vide (Tarragona, co-chair)
Antonio Sarasa (Madrid)
José-Luis Sierra (Madrid, co-chair)
Bianca Truthe (Magdeburg)
Florentina Lilica Voicu (Tarragona)

SUBMISSIONS:

Authors are invited to submit non-anonymized papers in English presenting
original and unpublished research. Papers should not exceed 12 single-spaced
pages (including eventual appendices) and should be formatted according to
the standard format for Springer 

Re: [Haskell-cafe] reifying typeclasses

2013-09-15 Thread oleg

Evan Laforge wrote:
 I have a typeclass which is instantiated across a closed set of 3
 types.  It has an ad-hoc set of methods, and I'm not too happy with
 them because being a typeclass forces them to all be defined in one
 place, breaking modularity.  A sum type, of course, wouldn't have that
 problem.  But in other places I want the type-safety that separate
 types provide, and packing everything into a sum type would destroy
 that.  So, expression problem-like, I guess.

 It seems to me like I should be able to replace a typeclass with
 arbitrary methods with just two, to reify the type and back.  This
 seems to work when the typeclass dispatches on an argument, but not on
 a return value.  E.g.:


If the universe (the set of types of interest to instantiate the type
class to) is closed, GADTs spring to mind immediately. See, for
example, the enclosed code. It is totally unproblematic (one should
remember to always write type signatures when programming with
GADTs. Weird error messages otherwise ensue.)

One of the most notable differences between GADT and type-class--based
programming is that GADTs are closed and type classes are open (that
is, new instances can be added at will). In fact, a less popular
technique of implementing type classes (which has been used in some Haskell
systems -- but not GHC)) is intensional type analysis, or typecase.
It is quite similar to the GADT solution.


The main drawback of the intensional type analysis as shown in the
enclosed code is that it breaks parametricity. The constraint Eq a
does not let one find out what the type 'a' is and so what other
operations it may support. (Eq a) says that the type a supports (==),
and does not say any more than that. OTH, Representable a tells quite
a lot about type a, essentially, everything.

 types.  It has an ad-hoc set of methods, and I'm not too happy with
 them because being a typeclass forces them to all be defined in one
 place, breaking modularity.  A sum type, of course, wouldn't have that
Why not to introduce several type classes, even a type class for each
method if necessary. Grouping methods under one type class is
appropriate when such a grouping makes sense. Otherwise, Haskell won't
lose in expressiveness if a type class could have only one method.

{-# LANGUAGE GADTs #-}

module G where

data TRep a where
TInt  :: TRep Int
TChar :: TRep Char

class Representable a where
repr :: TRep a

instance Representable Int where
repr = TInt

instance Representable Char where
repr = TChar

argument :: Representable a = a - Int
argument x = go repr x
 where
 -- For GADTs, signatures are important!
 go :: TRep a - a - Int
 go TInt  x = x
 go TChar x = fromEnum x

-- just the `mirror inverse'
result :: Representable a = Int - a
result x = go repr x
 where
 -- For GADTs, signatures are important!
 go :: TRep a - Int - a
 go TInt  x = x
 go TChar x = toEnum x

t1 = argument 'a'
t2 = show (result 98 :: Char)

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


Re: [Haskell-cafe] reifying typeclasses (resend)

2013-09-15 Thread Bas van Dijk
You can indeed use GADTs to solve this:

{-# LANGUAGE GADTs #-}

data Universe a where
UInt  :: Int  - Universe Int
UChar :: Char - Universe Char

class Universal a where
universe :: a - Universe a

instance Universal Int where
universe = UInt

instance Universal Char where
universe = UChar

argument :: (Universal a) = a - Int
argument x = case universe x of
   UInt  n - n
   UChar c - fromEnum c

result :: (Universal a) = Int - a
result val = x
  where
x = case universe x of
  UInt  _ - val
  UChar _ - toEnum val

On 15 September 2013 09:38, Evan Laforge qdun...@gmail.com wrote:
 [ This is the second time I sent this, the first time it said it was
 awaiting moderation because I'm not subscribed to haskell-cafe, which
 is weird because I thought I was.  Did a bunch of people get
 unsubscribed? ]

 I'm sure this is old-hat to typeclass wizards, but I've managed to get
 pretty far without understanding them too well, so here's a basic
 question.  I haven't seen it phrased this way before though:

 I have a typeclass which is instantiated across a closed set of 3
 types.  It has an ad-hoc set of methods, and I'm not too happy with
 them because being a typeclass forces them to all be defined in one
 place, breaking modularity.  A sum type, of course, wouldn't have that
 problem.  But in other places I want the type-safety that separate
 types provide, and packing everything into a sum type would destroy
 that.  So, expression problem-like, I guess.

 It seems to me like I should be able to replace a typeclass with
 arbitrary methods with just two, to reify the type and back.  This
 seems to work when the typeclass dispatches on an argument, but not on
 a return value.  E.g.:

 {-# LANGUAGE ScopedTypeVariables #-}

 class Taggable a where
 toTagged :: a - Tagged
 toTaggedType :: a - TaggedType
 fromTagged :: Tagged - Maybe a

 m_argument :: a - Int
 m_result :: Int - a

 data Tagged = TInt Int | TChar Char deriving (Show)
 data TaggedType = TypeInt | TypeChar deriving (Show)

 instance Taggable Int where
 toTagged = TInt
 toTaggedType _ = TypeInt
 fromTagged (TInt x) = Just x
 fromTagged _ = Nothing

 m_argument = id
 m_result = id

 instance Taggable Char where
 toTagged = TChar
 toTaggedType _ = TypeChar
 fromTagged (TChar x) = Just x
 fromTagged _ = Nothing

 m_argument = fromEnum
 m_result = toEnum

 argument :: (Taggable a) = a - Int
 argument a = case toTagged a of
 TInt x - x
 TChar c - fromEnum c

 result :: forall a. (Taggable a) = Int - a
 result val = case toTaggedType (undefined :: a) of
 TypeInt - val
 TypeChar - toEnum val


 Say m_argument and m_result are the ad-hoc methods I'd like to get out
 of the typeclass.  I can do that well enough for 'argument', but
 'result' runs into trouble.  One is the ugly undefined trick with
 toTaggedType, but the bigger one is that ghc says 'Could not deduce (a
 ~ Int) from the context (Taggable a)'.  I wasn't really expecting it
 to work, because it would entail a case with multiple types.  As far
 as I know, the only way for that to happen is with GADTs.  But I don't
 see how they could help me here.

 So, perhaps my intuition was wrong.  toTagged and fromTagged methods
 give you the power to go between value and type level, but apparently
 that's not enough power to express what typeclasses give you.  Also it
 seems like there's a fundamental difference between dispatching on
 argument vs dispatching on result.

 Is there a way to more formally understand the extents of what
 typeclasses provide, and what a toTagged fromTagged scheme gives me,
 so I can have a better intuition for how to go between value and type
 levels?

 Also, the toTaggedType thing is pretty ugly.  Not just passing it
 undefined, but how it has to repeat the types.  I don't really see a
 way to get around that though.
 ___
 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] reifying typeclasses

2013-09-15 Thread oleg

[I too had the problem sending this e-mail to Haskell list.
I got a reply saying the message awaits moderator approval]

Evan Laforge wrote:
 I have a typeclass which is instantiated across a closed set of 3
 types.  It has an ad-hoc set of methods, and I'm not too happy with
 them because being a typeclass forces them to all be defined in one
 place, breaking modularity.  A sum type, of course, wouldn't have that
 problem.  But in other places I want the type-safety that separate
 types provide, and packing everything into a sum type would destroy
 that.  So, expression problem-like, I guess.

 It seems to me like I should be able to replace a typeclass with
 arbitrary methods with just two, to reify the type and back.  This
 seems to work when the typeclass dispatches on an argument, but not on
 a return value.  E.g.:


If the universe (the set of types of interest to instantiate the type
class to) is closed, GADTs spring to mind immediately. See, for
example, the enclosed code. It is totally unproblematic (one should
remember to always write type signatures when programming with
GADTs. Weird error messages otherwise ensue.)

One of the most notable differences between GADT and type-class--based
programming is that GADTs are closed and type classes are open (that
is, new instances can be added at will). In fact, a less popular
technique of implementing type classes (which has been used in some Haskell
systems -- but not GHC)) is intensional type analysis, or typecase.
It is quite similar to the GADT solution.


The main drawback of the intensional type analysis as shown in the
enclosed code is that it breaks parametricity. The constraint Eq a
does not let one find out what the type 'a' is and so what other
operations it may support. (Eq a) says that the type a supports (==),
and does not say any more than that. OTH, Representable a tells quite
a lot about type a, essentially, everything.

 types.  It has an ad-hoc set of methods, and I'm not too happy with
 them because being a typeclass forces them to all be defined in one
 place, breaking modularity.  A sum type, of course, wouldn't have that
Why not to introduce several type classes, even a type class for each
method if necessary. Grouping methods under one type class is
appropriate when such a grouping makes sense. Otherwise, Haskell won't
lose in expressiveness if a type class could have only one method.

{-# LANGUAGE GADTs #-}

module G where

data TRep a where
TInt  :: TRep Int
TChar :: TRep Char

class Representable a where
repr :: TRep a

instance Representable Int where
repr = TInt

instance Representable Char where
repr = TChar

argument :: Representable a = a - Int
argument x = go repr x
 where
 -- For GADTs, signatures are important!
 go :: TRep a - a - Int
 go TInt  x = x
 go TChar x = fromEnum x

-- just the `mirror inverse'
result :: Representable a = Int - a
result x = go repr x
 where
 -- For GADTs, signatures are important!
 go :: TRep a - Int - a
 go TInt  x = x
 go TChar x = toEnum x

t1 = argument 'a'
t2 = show (result 98 :: Char)

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


[Haskell-cafe] An APL library for Haskell

2013-09-15 Thread Simon Peyton-Jones
Friends

Many of you will know the array language 
APLhttp://en.wikipedia.org/wiki/APL_%28programming_language%29.   It focuses 
on arrays and in particular has a rich, carefully-thought-out array algebra.

An obvious idea is: what would a Haskell library that embodies APL's array 
algebra look like?  In conversation with John Scholes and some of his 
colleagues in the APL community a group of us developed some ideas for a 
possible API, which you can find on the Haskell wiki here: 
http://www.haskell.org/haskellwiki/APL

However, we have all gone our separate ways, and I think it's entirely possible 
that that the idea will go no further.  So this message is to ask:

* Is anyone interested in an APL-style array library in Haskell?

* If so, would you like to lead the process of developing the API?

I think there are quite a few people who would be willing to contribute, 
including some core gurus from the APL community: John Scholes,  Arthur 
Whitney, and Roger Hui.

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


[Haskell-cafe] ANNOUNCE: New OpenGL packages

2013-09-15 Thread Sven Panne
New versions of the OpenGL packages are available on Hackage:

   * OpenGLRaw 1.4.0.0
   * GLURaw 1.4.0.0
   * OpenGL 2.9.0.0
   * GLUT 2.5.0.0

The mid-term goal is to make all these packages conform to the latest
OpenGL 4.4 specification, and while we're not yet there, this release
is nevertheless an important stepping stone towards that goal. The
packages contain a few non-backwards compatible changes, something
which is never nice for a public API, but it has been necessary:
OpenGL has come a long way from its initial fixed function pipeline to
its current form flexible form centered around shaders and buffers.
Because of this, a few design decisions on the Haskell side were not a
good fit anymore and simply had to change. Nevertheless, almost all
changes needed in the applications and libraries using the OpenGL
packages should be mechanical and straightforward. If not:
hope...@haskell.org is the place to get help if needed.

Hopefully the new packages will make it into the next Haskell Platform
release (2013.4.0.0), at least if I find out how to make it through
the proposal process... ;-)

Cheers,
   S.

P.S.: Here a list of the changes for each package:

==
Changes in the OpenGLRaw package
==

* Added support for the following extensions:

 GL_ARB_occlusion_query2
 GL_ARB_timer_query
 GL_ARB_draw_indirect
 GL_ARB_gpu_shader5
 GL_ARB_tesselllation_shader
 GL_ARB_transform_feedback3
 GL_ARB_ES2_compatibility
 GL_ARB_get_program_binary
 GL_ARB_separate_shader_objects
 GL_ARB_shader_atomic_counters
 GL_ARB_compute_shader
 GL_ARB_ES3_compatibility
 GL_ARB_framebuffer_no_attachments
 GL_ARB_shader_storage_buffer_object
 GL_ARB_query_buffer_object

* Added GLfixed type from OpenGL 4.1.

* Moved GLhandle type to
Graphics.Rendering.OpenGL.Raw.ARB.ShaderObjects where it belongs and
fixed its representation on Mac OS X.

* Added new Graphics.Rendering.OpenGL.Raw.Type module which exports
all GL types. Core31 and Core32 export only their respective subset
now.

* Correctly typed bitfield tokens as, well, GLbitfield instead of GLenum.

* Consistently use ‘Ptr a’ for ‘void*’ which are not opaque.

* Use ccall instead of stdcall on x86_64-windows.

* Use the OpenGLES framework on iOS.

==
Changes in the GLURaw package
==

* Use ccall instead of stdcall on x86_64-windows.

* Use the OpenGLES framework on iOS.

==
Changes in the OpenGL package
==

* Added sync object support.

* Added full support for OpenGL 4.4 query objects, extending and
changing the previous query object API a bit.

* Split ObjectName class into ObjectName + GeneratableObjectName
classes. Added single-name variants deleteObjectName and
genObjectName, they are a very common use case.

* Made BufferObject and TextureObject abstract. Now all GL objects
names are abstract and have to be explicitly generated. The only
exception is DisplayList, which is required to be non-abstract by the
spec.

* Shader is not a class anymore, but a data type with an ObjectName
instance and a creation action. Added ShaderType and shaderType.

* Added partial support for tessellation/geometry/compute shaders.

* Program is not a GeneratableObjectName, but has a createProgram
action now. Added attachShader and detachShader for incremental
changes.

* Deprecated shaderSource and added shaderSourceBS instead. Using
ByteString is more efficient and forces the caller to think about
encodings, e.g. via Data.Text.Encoding.

* Added support for shader/program binaries and shader precision queries.

* Revamped texture targets, adding partial support for texture buffer
objects and texture arrays.

* OpenGL 3.1 deprecated separate polygon draw modes, so use
GL_FRONT_AND_BACK internally in polygonMode whenever possible.

* Added missing Eq/Ord/Show instances for lots of data types.

* Simplified TransformFeedbackVaryings API, making it a bit more
similar to the one for activeAttribs and activeUniforms.

* Exported ContextProfile’.

* Renamed BlitFramebufferMask (to BlitBuffer) and its constructors.

* Renamed BufferRangeAccessBit (to MapBufferUsage) and its constructors

* Removed currentMatrix, genLists, deleteLists and isList, they have
been deprecated for ages.

* Full internal support for UTF-8.

* Do not expose internal #hidden modules.

* Lots of Haddock fixes and improvements.

* Renamed IndexedTransformFeedbackBuffer to IndexedTransformFeedbackBuffer.

* Fixed clip plane query.

==
Changes in the GLUT package

Re: [Haskell-cafe] An APL library for Haskell

2013-09-15 Thread Daniel Peebles
Interesting idea. It seems like building this on top of REPA would save a
lot of work, since it has a native notion of rank encoded in the type
system. I'd then see the APL-like combinators as a niche API for REPA,
rather than as a library of their own. And of course, you'd get
parallelization for free, more or less. I think some of the combinators on
that wiki page already have counterparts in the REPA API.




On Thu, Mar 8, 2012 at 8:44 AM, Simon Peyton-Jones simo...@microsoft.comwrote:

  Friends

 ** **

 Many of you will know the array language 
 APLhttp://en.wikipedia.org/wiki/APL_%28programming_language%29.
 It focuses on arrays and in particular has a rich, carefully-thought-out
 array algebra. 

 ** **

 An obvious idea is: *what would a Haskell library that embodies APL’s
 array algebra look like*?  In conversation with John Scholes and some of
 his colleagues in the APL community a group of us developed some ideas for
 a possible API, which you can find on the Haskell wiki here:
 http://www.haskell.org/haskellwiki/APL

 ** **

 However, we have all gone our separate ways, and I think it’s entirely
 possible that that the idea will go no further.  So this message is to ask:
 

 **· **Is anyone interested in an APL-style array library in
 Haskell?

 **· **If so, would you like to lead the process of developing the
 API?

 ** **

 I think there are quite a few people who would be willing to contribute,
 including some core gurus from the APL community: John Scholes,  Arthur
 Whitney, and Roger Hui.   

 ** **

 Simon

 ___
 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