[Haskell-cafe] SYB with Existentials

2010-05-26 Thread oleg

It is quite straightforward to extend the SYB generic programming
framework to existential data types, including existential data types
with type class constraints. After all, an existential is essentially
a variant data type with the infinite, in general, number of variants.

The only, non-fatal, problem is _not_ with writing the instance of
gunfold. Defining gunfold is easy. The problem is that the existing
SYB -- or, the module Data/Data.hs to be precise -- has
non-extensible constructor and datatype descriptions (Constr and
DataType). The problem is not fatal and can be worked around in
various inelegant ways. Alternatively, one can fix the problem once
and for all by making DataType and Constr extensible -- along the
lines of the new Exceptions. The following file

http://okmij.org/ftp/Haskell/DataEx.hs

demonstrates one such fix. The file DataEx.hs also tries to avoid the
overlap with Data.Typeable. (One doesn't need to carry the name of the
datatype's type constructor in DataType. That name can be obtained
from the result of typeOf). The file DataEx can be used alongside the
original Data.hs. The code below uses DataEx in that way, to
complement Data.hs. The hope is that the maintainers of SYB might
choose to extend Data.hs -- perhaps using some bits or ideas from
DataEx.hs.

The following is a complete literal Haskell code illustrating
gfold/gunfold for existentials.

 {-# LANGUAGE ExistentialQuantification, Rank2Types, ScopedTypeVariables #-}
 {-# LANGUAGE PatternGuards #-}
 {-# LANGUAGE DeriveDataTypeable #-}

 module SybExistential where

We import the old Data.Data and complement it with DataEx. We assume
that DataEx.hs present in the -i path.

 import Data.Generics (gnodecount)
 import Data.Data as Old
 import DataEx

-- The following is the sample existential data type suggested by
-- Oscar Finnsson. We use that data type as our running example.

 data DataBox = forall d. (Show d, Eq d, DataEx d) = DataBox d

We make the DataBox itself to be a member of Typeable, Eq and Show.

 instance Typeable DataBox where
   typeOf _ = mkTyConApp (mkTyCon DataBox) []

 instance Show DataBox where
 show (DataBox x) = DataBox[ ++ show x ++ ]

 -- Two databoxes are the same if the types of their enclosed values
 -- are the same, and their values are the same too
 instance Eq DataBox where
 DataBox x == DataBox y | Just y' - cast y = x == y'
 DataBox _ == DataBox _ = False


The file DataEx makes constructor representation extensible. We hereby
add a new variant to constructor representation, so to represent _any_
existential data type.

 data ExConstr = forall a. Typeable a = ExConstr a

 instance Show ExConstr where
 show (ExConstr a) = ExConstr ++ show (typeOf a)

 instance Typeable ExConstr where
   typeOf _ = mkTyConApp (mkTyCon ExConstr) []

 instance Eq ExConstr where
 ExConstr x == ExConstr y = typeOf x == typeOf y


We are now ready to implement gfold/gunfold for DataBox. First is
gfold; gfold is not affected by our extensions of Constr and is not
re-defined in DataEx.

 instance Old.Data DataBox where
gfoldl k z (DataBox d) = z DataBox `k` d


As the instance of DataType for DataBox we use a DataBox object
itself. DataBox is already a member of all needed classes (Eq, Show,
Typeable), except for the following.

The file DataEx.hs defines a Read-like type class to de-serialize
constructor representations. We don't need this feature here.

 instance ReadCtor DataBox where
 readConstr _ str = error not yet defined

We come to the main instance, of DataEx:

 instance DataEx DataBox where

As the `description' of DataBox's datatype we take a sample DataBox
value. We only care about typeOf of that value.

dataTypeOf _ = DataType (DataBox (undefined::Int))

Since an existential data type is a ``variant data type with,
generally, infinite number of data constructors'', we can use the very
value of the existential as the description of that particular
``constructor.''

toConstr = Constr . ExConstr

And finally, the definition of gunfold

gunfold k z (Constr c) | Just (ExConstr ec)- cast c,
 Just (DataBox (_::a)) - cast ec =
   k (z (DataBox::a - DataBox))


That is it. Here are a few tests.

 -- sample DataBoxes
 tdb1 = DataBox (42::Int)
 tdb2 = DataBox (string, tdb1)

 tdb2_show = show tdb2
 -- DataBox[(\string\,DataBox[42])]

The following tests use gfold

 tdb1_gcount = gnodecount tdb1
 -- 2

 tdb2_gcount = gnodecount tdb2
 -- 17

whereas the following tests use gunfold.


 -- generic ``minimum''
 -- (I took a liberty to define 0 as the min Int value, since
 -- it prints better)

 genMin :: DataEx a = a
 genMin = r
  where
  r = case DataEx.dataTypeOf r of DataType x - build . min_ctor $ x
  min_ctor x | Just (AlgDataType (c:_)) - cast x = Constr c
  min_ctor x | Just IntDataType  - cast x  = Constr . DataEx.IntConstr  $ 0
  min_ctor x | Just CharDataType - cast x  = Constr . DataEx.CharConstr $  
  min_ctor x | 

[Haskell-cafe] Work on Video Games in Haskell

2010-05-26 Thread Ryan Trinkle
iPwn Studios is seeking Haskell developers for its debut title, BloodKnight.

* No prior game development experience is required, but you must be very
comfortable working in Haskell.
* Compensation is negotiable; profit-sharing may be available in some cases.
* To apply, or for more information, contact me at r...@ipwnstudios.com.

BloodKnight is an action-roleplaying game inspired by games like Diablo and
Fallout.  It is currently in the final stages of development, and will be
released later this year on a variety of smartphone platforms, including
iPhone and Android.

iPwn Studios is a start-up company located in Boston, MA.  We believe in
giving back to the Haskell community, so we've open-sourced our ghc-iphone
project, which allows GHC to produce binaries for the iPhone.  Check it out
at http://projects.haskell.org/ghc-iphone/.


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


Re: [Haskell-cafe] Work on Video Games in Haskell

2010-05-26 Thread Lyndon Maydwell
This sounds fantastic. Now I wish I had started learning haskell a few
years earlier.

As a side note, how is this project getting around the language
restrictions apple put in the developer license agreement?

--- [http://daringfireball.net/2010/04/iphone_agreement_bans_flash_compiler]
In the new version of the iPhone Developer Program License Agreement
released by Apple today (and which developers must agree to before
downloading the 4.0 SDK beta), section 3.3.1 now reads:

3.3.1 — Applications may only use Documented APIs in the manner
prescribed by Apple and must not use or call any private APIs.
Applications must be originally written in Objective-C, C, C++, or
JavaScript as executed by the iPhone OS WebKit engine, and only code
written in C, C++, and Objective-C may compile and directly link
against the Documented APIs (e.g., Applications that link to
Documented APIs through an intermediary translation or compatibility
layer or tool are prohibited).
---

On Wed, May 26, 2010 at 2:52 PM, Ryan Trinkle
ryan.trin...@ipwnstudios.com wrote:
 iPwn Studios is seeking Haskell developers for its debut title, BloodKnight.
 * No prior game development experience is required, but you must be very
 comfortable working in Haskell.
 * Compensation is negotiable; profit-sharing may be available in some cases.
 * To apply, or for more information, contact me at r...@ipwnstudios.com.
 BloodKnight is an action-roleplaying game inspired by games like Diablo and
 Fallout.  It is currently in the final stages of development, and will be
 released later this year on a variety of smartphone platforms, including
 iPhone and Android.
 iPwn Studios is a start-up company located in Boston, MA.  We believe in
 giving back to the Haskell community, so we've open-sourced our ghc-iphone
 project, which allows GHC to produce binaries for the iPhone.  Check it out
 at http://projects.haskell.org/ghc-iphone/.

 Ryan Trinkle
 iPwn Studios

 ___
 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] Work on Video Games in Haskell

2010-05-26 Thread David Virebayre
On Wed, May 26, 2010 at 9:23 AM, Lyndon Maydwell maydw...@gmail.com wrote:

 As a side note, how is this project getting around the language
 restrictions apple put in the developer license agreement?

From the project page :

This version uses Apple's official iPhone SDK as its back end compiler.

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


Re: [Haskell-cafe] [reactive] A pong and integrate

2010-05-26 Thread Limestraël
 The GHC bugs are now fixed, so it might be stable enough for
 another adventure like that, but I don't think I would bet on it
 again.

GHC bugs are corrected, but Reactive still have some. (See my previous
posts)

 IMO Haskell is great for writing small clean prototypes, doing
 interesting research, and maybe making some fun little games, but I
 wouldn't use it for production reactive game coding, not yet at least.

Tim Sweeney (from Epic Games) has another perspective about that [1].
Besides, FRP is not mandatory. You can always make games in Haskell by using
a more regular style (more imperative, would some say).
For now, the main problem is the small number of Haskell libraries for games
when compared to the huge numbers of those which exist in C++, which
prevents, for now, Haskell to be used as the main language for big
commercial games.
But for smaller scale games (like indie), which have less needs, I think
it's worth it.


[1]
http://www.scribd.com/doc/5687/The-Next-Mainstream-Programming-Language-A-Game-Developers-Perspective-by-Tim-Sweeney

2010/5/25 Peter Verswyvelen bugf...@gmail.com

 Well, first of all, I did not make these PS3 visualization, my former
 colleagues and I just made the editor, language and runtime that
 allowed video game artists to do the job for us in a couple of weeks
 time :-)

 I wouldn't use Yampa, for performance reasons, and difficulty to get
 it running on alien platforms (it is well known it performs relatively
 badly, although the work done by Paul Liu and co on Causal Commutative
 Arrows looks very promising, but does not support dynamic switching
 yet). After all, Yampa models a synchronous dataflow language, and
 compilers for these languages are relatively easy to make IMO.

 My previous - now defunct -  company Anygma spent a lot of money on
 trying to use Haskell and Reactive for game programming, which
 unfortunately ended in some nasty GHC bugs popping up (see
 http://www.haskell.org/haskellwiki/Unamb), and not all problems with
 Reactive got fixed; it is amazing how difficult this all turned out to
 be. The GHC bugs are now fixed, so it might be stable enough for
 another adventure like that, but I don't think I would bet on it
 again.

 IMO Haskell is great for writing small clean prototypes, doing
 interesting research, and maybe making some fun little games, but I
 wouldn't use it for production reactive game coding, not yet at least.


 On Tue, May 25, 2010 at 10:49 AM, Limestraël limestr...@gmail.com wrote:
  Wow... impressive...
 
  And now, with your experience, if you'd have to do this again, would you
 use
  Yampa or stick up with C#/C++ ?
 
  2010/5/24 Peter Verswyvelen bugf...@gmail.com
 
  Yeah. Funny that we're still writing games in C++, while mission
  critical and hard real time systems are written in much nicer
  languages :)
 
  I made something similar to Lucid Synchrone for a game company I used
  to work, but with the purpose of making reactive programming
  accessible to computer artists. The integrated development environment
  provided the typical boxes-and-links user interface, where the boxes
  were signal functions. Signals itself were not exposed, like Yampa.
  The system did type inference so artists never really had to deal with
  types. Special nodes like feedback and delay where provided to allow
  transferring values to the next frame. This actually was a great
  success, digital artists could literally create little interactive
  applications with it, without much  help from programmers. This
  resulted in a Playstation 3 visual experience Mesmerize
  (http://www.youtube.com/watch?v=rW7qGhBjwhY). This was before I knew
  Haskell or functional programming, so it was hacked together in C# and
  C++...
 
  I still believe that the reason why computers artists could work with
  this environment and were not able to learn imperative programming is
  functional programming itself: the system had all the goodies of FP:
  type inference, referential transparancy, etc... But is also provided
  the possibility to edit literals while the simulation was running,
  providing zero turnaround times, which was equally important for quick
  adoption of the software.
 
  So IMO Haskell and FRP systems have a huge potential for education of
  a much broader audience than just computer scientists...
 
 
 
 
 
  On Mon, May 24, 2010 at 6:13 PM, Limestraël limestr...@gmail.com
 wrote:
   I assumed also that it was a field which was still under research,
   however,
   Lustre, again, is used for critical control software in aircraft,
   helicopters, and nuclear power plants, according to wikipedia.
 
 

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


Re: [Haskell] Re: [Haskell-cafe] Work on Video Games in Haskell

2010-05-26 Thread Brandon S. Allbery KF8NH

On May 26, 2010, at 03:50 , David Virebayre wrote:
On Wed, May 26, 2010 at 9:23 AM, Lyndon Maydwell  
maydw...@gmail.com wrote:

As a side note, how is this project getting around the language
restrictions apple put in the developer license agreement?



From the project page :


This version uses Apple's official iPhone SDK as its back end  
compiler.


You might want to reread that license agreement.  Specifically:

Applications must be originally written in Objective-C, C, C++, or
JavaScript as executed by the iPhone OS WebKit engine, and only code
written in C, C++, and Objective-C may compile and directly link
against the Documented APIs (e.g., Applications that link to
Documented APIs through an intermediary translation or compatibility
layer or tool are prohibited)

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell] Re: [Haskell-cafe] Work on Video Games in Haskell

2010-05-26 Thread David Virebayre
On Wed, May 26, 2010 at 9:58 AM, Brandon S. Allbery KF8NH
allb...@ece.cmu.edu wrote:

 You might want to reread that license agreement.  Specifically:

 Applications must be originally written in Objective-C, C, C++, or
 JavaScript as executed by the iPhone OS WebKit engine, and only code
 written in C, C++, and Objective-C may compile and directly link
 against the Documented APIs (e.g., Applications that link to
 Documented APIs through an intermediary translation or compatibility
 layer or tool are prohibited)

Ah, yes. Ouch, that's abusive.
Can they tell the difference though ?

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


Re: [Haskell] Re: [Haskell-cafe] Work on Video Games in Haskell

2010-05-26 Thread Daniel Peebles
Of course, given that they have no way of determining that short of asking
for the source code (and hiring another thousand reviewers to read it) or
applying static analysis tools with heuristics to the programs. I really
doubt they do the latter, and the former is unrealistic.

Most people seem to think the clause is there mostly to discourage large
companies like Adobe from making generic tools to translate to the
iPhone/iPad. It would be a lot of effort for Apple to actually enforce it
strictly.

On Wed, May 26, 2010 at 3:58 AM, Brandon S. Allbery KF8NH 
allb...@ece.cmu.edu wrote:

 On May 26, 2010, at 03:50 , David Virebayre wrote:

 On Wed, May 26, 2010 at 9:23 AM, Lyndon Maydwell maydw...@gmail.com
 wrote:

 As a side note, how is this project getting around the language
 restrictions apple put in the developer license agreement?


  From the project page :


 This version uses Apple's official iPhone SDK as its back end compiler.


 You might want to reread that license agreement.  Specifically:


 Applications must be originally written in Objective-C, C, C++, or
 JavaScript as executed by the iPhone OS WebKit engine, and only code
 written in C, C++, and Objective-C may compile and directly link
 against the Documented APIs (e.g., Applications that link to
 Documented APIs through an intermediary translation or compatibility
 layer or tool are prohibited)

 --
 brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
 system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
 electrical and computer engineering, carnegie mellon universityKF8NH



 ___
 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] Re: [Haskell-cafe] Work on Video Games in Haskell

2010-05-26 Thread Brandon S. Allbery KF8NH

On May 26, 2010, at 04:14 , David Virebayre wrote:

On Wed, May 26, 2010 at 9:58 AM, Brandon S. Allbery KF8NH
allb...@ece.cmu.edu wrote:

You might want to reread that license agreement.  Specifically:


Ah, yes. Ouch, that's abusive.
Can they tell the difference though ?



I suspect GHC-generated code is fairly distinctive even as machine  
code.  But they don't have to go to that extent; all they have to do  
is use Google to find this thread.  :(


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] MultiParamClasses question

2010-05-26 Thread Eugeny N Dzhurinsky
On Tue, May 25, 2010 at 10:46:47PM +0100, Stephen Tetley wrote:
 Hi Eugene
 
 You can store different things in a Map by collecting them with a
 simple 'sum' type:

Hello, Stephen!

The records to be stored into a Map are not related to each other. So wrapping
them into another type is not very smart solution in my case :)

The problem is really with the fact that records, created from such lines

user_1_name=user
group_1_name=group

do refer to the same key 1. But you gave me idea that I can use single map -
but as a key use something like 

type KeyT k i = (k,i)

where k is type of record (Group or User), and i is index, usually Int.

This way I will try to redesign my existing code.

Thank you for the idea :)

-- 
Eugene Dzhurinsky


pgpekoWNsf3na.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell] Re: [Haskell-cafe] Work on Video Games in Haskell

2010-05-26 Thread Ryan Trinkle
Hi guys,

I don't think this licensing issue will be a problem for us.  It's not clear
to me that our game violates this new term, and we certainly don't violate
any of the principles Steve Jobs used to justify it.  If Apple wants to
reject our app, they already have a variety of excuses at their disposal, as
they've demonstrated on many occasions.  Frankly, it'd be their loss;
Android is now the fastest-growing smartphone market, and we'll be more than
happy to focus on it (and other friendlier markets) if Apple's not
interested in having our product on their platform.


Ryan Trinkle
iPwn Studios

On Wed, May 26, 2010 at 4:18 AM, Brandon S. Allbery KF8NH 
allb...@ece.cmu.edu wrote:

 On May 26, 2010, at 04:14 , David Virebayre wrote:

 On Wed, May 26, 2010 at 9:58 AM, Brandon S. Allbery KF8NH
 allb...@ece.cmu.edu wrote:

 You might want to reread that license agreement.  Specifically:


 Ah, yes. Ouch, that's abusive.
 Can they tell the difference though ?



 I suspect GHC-generated code is fairly distinctive even as machine code.
  But they don't have to go to that extent; all they have to do is use Google
 to find this thread.  :(


 --
 brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
 system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
 electrical and computer engineering, carnegie mellon universityKF8NH



 ___
 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] [reactive] A pong and integrate

2010-05-26 Thread Sam Martin
I work in the games industry and I'm also not convinced of the Haskell+FRP path 
for games, but for different reasons. I am very fond of Haskell for games 
however, and think it is achievable. 

 

Regarding FRP, I don't think it is the right framework to base a game on. It's 
great for some stuff, particularly the kind of problem Peter demonstrated, but 
games are a lot more varied than that and efficiency concerns aside, it's just 
not the right approach for everything. I see it more as a useful tool for some 
elements than a framework that should form the backbone of a game.

 

Functional programming on the other hand is a big thing. Games look a lot more 
functional now days than they ever did before, and C++ doesn't have the right 
vocabulary to allow you to scratch this itch properly. EDSLs, parallelism, 
composability, higher order functions, and static typing are really where it's 
at, and Haskell excels at this. There's a lot of missed opportunities for more 
elegant and powerful architectures going by at the moment simple because it's 
not realistic to attempt them in C/C++. 

 

One area where Haskell is not so hot and needs a bit of TLC is it's 
'embedability'. A large cross-platform 100% Haskell game is not on the cards at 
the moment, but Haskell could start getting its hands dirty, if only it could 
be sensibly embedded within an otherwise C++ app. This would allow people to 
start to take advantage of it, without some wholesale switch over. However, to 
do this, Haskell implementations at least need to be more compiler and platform 
agnostic, and we would probably need a lot more control over the Haskell 
runtime itself, particularly wrt memory handling. Lua (which is very popular in 
the games industry) and ATS (which isn't used to my knowledge, but has 
excellent interaction with C) are good examples of languages where this kind of 
thing is considerably easier. Haskell would have to fit in differently to this, 
but that's the kind of idea.

 

Interesting things to note are that in this scenario, you could probably ditch 
IO altogether and just embed 'pure' Haskell. Games have very limited IO which 
would likely be best handed in C++ anyway.

 

Laziness/space leaks, garbage collection and general performance concerns are 
obviously also issues, but that's for another day J

 

Cheers,

Sam

 

From: haskell-cafe-boun...@haskell.org 
[mailto:haskell-cafe-boun...@haskell.org] On Behalf Of Limestraël
Sent: 26 May 2010 08:52
To: Peter Verswyvelen
Cc: haskell-cafe@haskell.org; Patai Gergely
Subject: Re: [Haskell-cafe] [reactive] A pong and integrate

 

 The GHC bugs are now fixed, so it might be stable enough for
 another adventure like that, but I don't think I would bet on it
 again.

GHC bugs are corrected, but Reactive still have some. (See my previous posts)

 IMO Haskell is great for writing small clean prototypes, doing
 interesting research, and maybe making some fun little games, but I
 wouldn't use it for production reactive game coding, not yet at least.

Tim Sweeney (from Epic Games) has another perspective about that [1].
Besides, FRP is not mandatory. You can always make games in Haskell by using a 
more regular style (more imperative, would some say).
For now, the main problem is the small number of Haskell libraries for games 
when compared to the huge numbers of those which exist in C++, which prevents, 
for now, Haskell to be used as the main language for big commercial games.
But for smaller scale games (like indie), which have less needs, I think it's 
worth it.


[1] 
http://www.scribd.com/doc/5687/The-Next-Mainstream-Programming-Language-A-Game-Developers-Perspective-by-Tim-Sweeney

2010/5/25 Peter Verswyvelen bugf...@gmail.com

Well, first of all, I did not make these PS3 visualization, my former
colleagues and I just made the editor, language and runtime that
allowed video game artists to do the job for us in a couple of weeks
time :-)

I wouldn't use Yampa, for performance reasons, and difficulty to get
it running on alien platforms (it is well known it performs relatively
badly, although the work done by Paul Liu and co on Causal Commutative
Arrows looks very promising, but does not support dynamic switching
yet). After all, Yampa models a synchronous dataflow language, and
compilers for these languages are relatively easy to make IMO.

My previous - now defunct -  company Anygma spent a lot of money on
trying to use Haskell and Reactive for game programming, which
unfortunately ended in some nasty GHC bugs popping up (see
http://www.haskell.org/haskellwiki/Unamb), and not all problems with
Reactive got fixed; it is amazing how difficult this all turned out to
be. The GHC bugs are now fixed, so it might be stable enough for
another adventure like that, but I don't think I would bet on it
again.

IMO Haskell is great for writing small clean prototypes, doing
interesting research, and maybe making some fun little games, but I
wouldn't use it for production reactive 

Re: [Haskell-cafe] Re: currying combinators

2010-05-26 Thread Yitzchak Gale
I wrote:
 keep :: ((t -  b) -  u -  b) -  ((t1 -  t) -  b) -  (t1 -  u) - b
 so then
 nameZip = keep (drop' . drop') names

Günther Schmidt wrote:
 don't be tease man, show me what you got :)

Ivan Miljenovic wrote:
 Methinks Yitzchak made a typo

Yes, sorry about that. Tested in ghci this time :).

keep :: (forall c . (t -  c) -  u -  c) -  ((t1 -  t) -  b) -
(t1 -  u) - b
keep transform rec = \fn - rec $ transform id . fn

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


[Haskell-cafe] Unicode vs. System.Directory

2010-05-26 Thread Arie Peterson
After upgrading to haskell-platform-2010.1.0.0, with the improved unicode
support for IO in ghc-6.12, I hoped to be able to deal with filenames
containing non-ascii characters. This still seems problematic, though:

$ ls
m×n♯α
$ ghci
GHCi, version 6.12.1: http://www.haskell.org/ghc/  :? for help
Prelude :m +System.Directory 
Prelude System.Directory getDirectoryContents . = mapM_ putStrLn
..
mÃnâ¯Î±
.

I hope this passes through the various email systems unharmed; on my
terminal, the output of 'ls' contains shiny unicode characters, while
'ghci' garbles up the filename. (My locale is en_GB.utf8.)

Similar problems arise with functions such as 'copyFile', which refuses to
handle filenames with non-ascii characters (unless wrapping it with
encoding functions).


Is this a known problem? I searched ghc's trac, but there are no relevant
bugs for the component 'libraries/directory'.


I have parts of a unicode-aware layer on top of System.Directory laying
around somewhere. I was rather hoping to ditch it, but I can polish it and
put it on hackage, if people are interested.


Kind regards,

Arie

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


Re: [Haskell-cafe] Re: currying combinators

2010-05-26 Thread Yitzchak Gale
I wrote:
 keep :: (forall c . (t -  c) -  u -  c) -  ((t1 -  t) -  b) - (t1 -  
 u) - b
 keep transform rec = \fn - rec $ transform id . fn

Just to clarify - you don't really need the RankNTypes here, I just
wrote it that way so you could see what I had been thinking,
and to make it clear how the first parameter of keep
takes transformers like drop'. But you could write it as

keep :: ((t - t) - u - t) - ...

and it would work just fine, because transformers like drop'
would specialize nicely to what you need for keep.

If you let GHC deduce the type of keep from its definition,
GHC comes up with something else:

keep :: ((a - a) - u - t) - ((t1 - t) - b) - (t1 - u) - b

That also works, but it's weird. It generalizes in a direction
that we don't really need here, and thus obscures the meaning
of what we're doing.

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


Re: [Haskell-cafe] Unicode vs. System.Directory

2010-05-26 Thread Johan Tibell
On Wed, May 26, 2010 at 1:25 PM, Arie Peterson ar...@xs4all.nl wrote:

 Is this a known problem? I searched ghc's trac, but there are no relevant
 bugs for the component 'libraries/directory'.


This bug might be relevant:

http://hackage.haskell.org/trac/ghc/ticket/3307
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Unicode vs. System.Directory

2010-05-26 Thread Yitzchak Gale
Arie Peterson wrote:
 After upgrading to haskell-platform-2010.1.0.0, with the improved unicode
 support for IO in ghc-6.12, I hoped to be able to deal with filenames
 containing non-ascii characters. This still seems problematic, though

Yes, unfortunately. This is not simple to fix, for several
reasons:

o The impedance mismatch between various operating
  systems and file systems about how filenames are
  represented internally w.r.t. Unicode

o Haskell 98, which specifies that a FilePath is a
  String, i.e., Unicode

o Backwards compatibility with existing Haskell
  implementations, which abuse the String type
  and represent bytes in a file path as if they
  were Unicode characters

Johan Tibell wrote:
 This bug might be relevant:
 http://hackage.haskell.org/trac/ghc/ticket/3307

#3307 System.IO and System.Directory functions
  not Unicode-aware under Unix

Related bugs:

#3308 getArgs should return Unicode on Windows
#3309 getArgs should return Unicode on Unix
#4006 System.Process doesn't encode its arguments.

See the linked discussions in those bugs for
a lot more details, and various ideas about how
to proceed.

I hope your pinging this issue will bring it closer to
being resolved. It's important.

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


Re: [Haskell] Re: [Haskell-cafe] Work on Video Games in Haskell

2010-05-26 Thread Pierre-Etienne Meunier
Anyway, does the license imply that one can't compile GHC's core language and 
RTS into objective-c, then compile it with their so great software ?



El 26/05/2010, a las 05:51, Ryan Trinkle escribió:

 Hi guys,
 
 I don't think this licensing issue will be a problem for us.  It's not clear 
 to me that our game violates this new term, and we certainly don't violate 
 any of the principles Steve Jobs used to justify it.  If Apple wants to 
 reject our app, they already have a variety of excuses at their disposal, as 
 they've demonstrated on many occasions.  Frankly, it'd be their loss; Android 
 is now the fastest-growing smartphone market, and we'll be more than happy to 
 focus on it (and other friendlier markets) if Apple's not interested in 
 having our product on their platform.
 
 
 Ryan Trinkle
 iPwn Studios
 
 On Wed, May 26, 2010 at 4:18 AM, Brandon S. Allbery KF8NH 
 allb...@ece.cmu.edu wrote:
 On May 26, 2010, at 04:14 , David Virebayre wrote:
 On Wed, May 26, 2010 at 9:58 AM, Brandon S. Allbery KF8NH
 allb...@ece.cmu.edu wrote:
 You might want to reread that license agreement.  Specifically:
 
 Ah, yes. Ouch, that's abusive.
 Can they tell the difference though ?
 
 
 I suspect GHC-generated code is fairly distinctive even as machine code.  But 
 they don't have to go to that extent; all they have to do is use Google to 
 find this thread.  :(
 
 
 -- 
 brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
 system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
 electrical and computer engineering, carnegie mellon universityKF8NH
 
 
 
 ___
 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] Re: [Haskell-cafe] Work on Video Games in Haskell

2010-05-26 Thread Liam O'Connor
If you guys get a nice library layer going between the Java APIs and
Android NDK Haskell, I would very much like it if you could post it up
somewhere. I think the entire community could benefit.

Cheers.
~Liam



On 26 May 2010 19:51, Ryan Trinkle ryan.trin...@ipwnstudios.com wrote:
 Hi guys,
 I don't think this licensing issue will be a problem for us.  It's not clear
 to me that our game violates this new term, and we certainly don't violate
 any of the principles Steve Jobs used to justify it.  If Apple wants to
 reject our app, they already have a variety of excuses at their disposal, as
 they've demonstrated on many occasions.  Frankly, it'd be their loss;
 Android is now the fastest-growing smartphone market, and we'll be more than
 happy to focus on it (and other friendlier markets) if Apple's not
 interested in having our product on their platform.

 Ryan Trinkle
 iPwn Studios
 On Wed, May 26, 2010 at 4:18 AM, Brandon S. Allbery KF8NH
 allb...@ece.cmu.edu wrote:

 On May 26, 2010, at 04:14 , David Virebayre wrote:

 On Wed, May 26, 2010 at 9:58 AM, Brandon S. Allbery KF8NH
 allb...@ece.cmu.edu wrote:

 You might want to reread that license agreement.  Specifically:

 Ah, yes. Ouch, that's abusive.
 Can they tell the difference though ?


 I suspect GHC-generated code is fairly distinctive even as machine code.
  But they don't have to go to that extent; all they have to do is use Google
 to find this thread.  :(

 --
 brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
 system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
 electrical and computer engineering, carnegie mellon university    KF8NH



 ___
 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] [reactive] A pong and integrate

2010-05-26 Thread David Sankel
On Wed, May 26, 2010 at 6:19 AM, Sam Martin sam.mar...@geomerics.comwrote:

  There’s a lot of missed opportunities for more elegant and powerful
 architectures going by at the moment simple because it’s not realistic to
 attempt them in C/C++.

I beg to differ on that point. See my presentation[1]/paper[2] I gave at
boostcon a couple weeks ago. I have successfully used C++ as a functional
language in multiple production software applications, including FRP
designs.

[1] http://www.filetolink.com/c109d02b
[2] http://www.filetolink.com/ff94ea7e

David

-- 
David Sankel
Sankel Software
www.sankelsoftware.com
585 617 4748 (Office)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] currying combinators

2010-05-26 Thread Lennart Augustsson
There are no interesting (i.e. total) functions of that type.

2010/5/25 Yitzchak Gale g...@sefer.org:
 Günther Schmidt wrote:
 http://www.hpaste.org/fastcgi/hpaste.fcgi/view?id=25694
 in which I attempt to develop a currying combinator library.
 I'm stuck at some point and would appreciate any help.

 How about this:

 keep :: ((t - b) - u - b) - ((t1 - t) - b) - (t1 - u) - b

 so then

 nameZip = keep (drop' . drop') names

 Regards,
 Yitz
 ___
 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] Re: [Haskell-cafe] Work on Video Games in Haskell

2010-05-26 Thread Edward Kmett
On Wed, May 26, 2010 at 5:51 AM, Ryan Trinkle
ryan.trin...@ipwnstudios.comwrote:

 Hi guys,

 I don't think this licensing issue will be a problem for us.  It's not
 clear to me that our game violates this new term, and we certainly don't
 violate any of the principles Steve Jobs used to justify it.  If Apple wants
 to reject our app, they already have a variety of excuses at their disposal,
 as they've demonstrated on many occasions.  Frankly, it'd be their loss;
 Android is now the fastest-growing smartphone market, and we'll be more than
 happy to focus on it (and other friendlier markets) if Apple's not
 interested in having our product on their platform.


Steve Jobs has been quite clear that apps written in other languages, even
ones that are interpreted in, compiles down to or otherwise generate
objective c source code, don't comply with the changes in section 3.3.1 of
their license, so I'm not sure that you have much of a case.

 “We’ve been there before, and intermediate layers between the platform and
 the developer ultimately produces sub-standard apps and hinders the progress
 of the platform.”

Read more:
http://techcrunch.com/2010/04/10/steve-jobs-responds-to-iphone-sdk-complaints-intermediate-layers-produce-sub-standard-apps/#ixzz0p3gfoNZI

Haskell definitely qualifies as an 'intermediate layer', just like
MonoTouch, and just like the Flash-to-Objective-C compiler that provoked the
original response from Apple.

http://www.taoeffect.com/blog/2010/04/steve-jobs-response-a-brief-followup/

Heck, even libraries that may contain scripting and modeling utilities like
Unity3d are in jeopardy, due to this cockamamie restriction, which threatens
to send the art of level design and game programming for the iphone
technologically clear back into the early 90s, though at least there they
appear to be treading lightly, since Unity has been useful in providing the
iphone with a lot of high end content.

http://answers.unity3d.com/questions/7408/is-unity3d-banned-by-new-apple-sdk-licence

But, there are other numerous discussions floating around in the blogosphere
involving previously approved applications written in scheme (even compiled
via objective c), c#, or other middleware languages having their
applications removed from the app store.

So, sadly, I think your chances of shipping your a title written in Haskell
on the iPhone are shot to hell.

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


Re: [Haskell-cafe] [reactive] A pong and integrate

2010-05-26 Thread Pierre-Etienne Meunier
Well, this does not contradict Sam's point, which was that you may have written 
nicer, faster and more elegant code in way less time, had you used a true 
programming language ;-)



El 26/05/2010, a las 12:28, David Sankel escribió:

 On Wed, May 26, 2010 at 6:19 AM, Sam Martin sam.mar...@geomerics.com wrote:
 There’s a lot of missed opportunities for more elegant and powerful 
 architectures going by at the moment simple because it’s not realistic to 
 attempt them in C/C++.
 
 I beg to differ on that point. See my presentation[1]/paper[2] I gave at 
 boostcon a couple weeks ago. I have successfully used C++ as a functional 
 language in multiple production software applications, including FRP designs.
 
 [1] http://www.filetolink.com/c109d02b
 [2] http://www.filetolink.com/ff94ea7e
 
 David
 
 -- 
 David Sankel
 Sankel Software
 www.sankelsoftware.com
 585 617 4748 (Office)
 ___
 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] Re: [Haskell-cafe] Work on Video Games in Haskell

2010-05-26 Thread Brandon S. Allbery KF8NH

On May 26, 2010, at 10:17 , Pierre-Etienne Meunier wrote:
Anyway, does the license imply that one can't compile GHC's core  
language and RTS into objective-c, then compile it with their so  
great software ?


As I read it, yes; it says that the calls to their APIs must  
*originate* from permitted languages, and specifically prohibits using  
those languages via translation layers.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] currying combinators

2010-05-26 Thread David Sankel
keep :: ((t - b) - u - b) - ((t1 - t) - b) - (t1 - u) - b

On Wed, May 26, 2010 at 12:49 PM, Lennart Augustsson lenn...@augustsson.net
 wrote:

 There are no interesting (i.e. total) functions of that type.


I wonder how one would prove that to be the case. I tried and didn't come up
with anything.

David

-- 
David Sankel
Sankel Software
www.sankelsoftware.com
585 617 4748 (Office)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell] Re: [Haskell-cafe] Work on Video Games in Haskell

2010-05-26 Thread Evan Laforge
 So, sadly, I think your chances of shipping your a title written in Haskell
 on the iPhone are shot to hell.

+1 for the android version.

Disclaimer: biased google employee

:P

Unfortunately then you get another cockamamie restriction in the whole
JVM vs. tail calls thing...  but if you can get around that then lots
of people will like you a lot.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell] Re: [Haskell-cafe] Work on Video Games in Haskell

2010-05-26 Thread Pierre-Etienne Meunier
Well in this case I'd be really interested in seeing how the can tell the 
difference, be it only from a simple complexity theoretic point of view ! I 
understand they may look for common patterns in their compiler code to tell the 
difference between GHC's generated code and theirs, but pretending they can do 
it in this case only shows that Apple lawyers never communicate with the 
engineers.



El 26/05/2010, a las 15:32, Brandon S. Allbery KF8NH escribió:

 On May 26, 2010, at 10:17 , Pierre-Etienne Meunier wrote:
 Anyway, does the license imply that one can't compile GHC's core language 
 and RTS into objective-c, then compile it with their so great software ?
 
 As I read it, yes; it says that the calls to their APIs must *originate* from 
 permitted languages, and specifically prohibits using those languages via 
 translation layers.
 
 -- 
 brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
 system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
 electrical and computer engineering, carnegie mellon universityKF8NH
 
 

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


Re: [Haskell] Re: [Haskell-cafe] Work on Video Games in Haskell

2010-05-26 Thread Dan Mead
wouldn't they just want to have TCO happen during the compilation into
java? why would you want to output java that has recursion?

-Dan

On Wed, May 26, 2010 at 4:17 PM, Evan Laforge qdun...@gmail.com wrote:
 So, sadly, I think your chances of shipping your a title written in Haskell
 on the iPhone are shot to hell.

 +1 for the android version.

 Disclaimer: biased google employee

 :P

 Unfortunately then you get another cockamamie restriction in the whole
 JVM vs. tail calls thing...  but if you can get around that then lots
 of people will like you a lot.
 ___
 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] Re: [Haskell-cafe] Work on Video Games in Haskell

2010-05-26 Thread Brandon S. Allbery KF8NH

On May 26, 2010, at 17:22 , Pierre-Etienne Meunier wrote:
Well in this case I'd be really interested in seeing how the can  
tell the difference, be it only from a simple complexity theoretic  
point of view ! I understand they may look for common patterns in  
their compiler code to tell the difference between GHC's generated  
code and theirs, but pretending they can do it in this case only  
shows that Apple lawyers never communicate with the engineers.



No clue how they might be planning to enforce it, but it's not like  
the lawyers care; it's up to Apple to decide if they want to pursue  
any individual possible case of infringement, and Jobs to figure out  
what kind of hole he's dug himself into.  :)


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Math questions

2010-05-26 Thread Pete Chown

Mujtaba Boori wrote:


Define a higher order function  that tests whether two functions , both
defined on integers , coincide for all integers between 1 and 100


If this really is a homework question, I dare you to submit this 
solution.  Try it for yourself, it works fine. :-)


module Main where

import Control.Monad
import Data.IORef
import System.IO.Unsafe

forLoop :: Int - Int - (Int - IO ()) - IO ()
forLoop start stop body = mapM_ body [start..stop]

test :: (Eq a) = (Int - a) - (Int - a) - Bool
test f1 f2 = unsafePerformIO $ do
goodSoFar - newIORef True
forLoop 1 100 $ \i -
  when (f1 i /= f2 i) $ writeIORef goodSoFar False
readIORef goodSoFar

testFunc1 27 = numpty
testFunc1 i = show i

testFunc2 270 = numpty
testFunc2 i = show i

main = do
  print $ test show testFunc1
  print $ test show testFunc2

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


Re: [Haskell] Re: [Haskell-cafe] Work on Video Games in Haskell

2010-05-26 Thread John Meacham
On Wed, May 26, 2010 at 01:17:00PM -0700, Evan Laforge wrote:
 Unfortunately then you get another cockamamie restriction in the whole
 JVM vs. tail calls thing...  but if you can get around that then lots
 of people will like you a lot.

Working on it... :)

John

-- 
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Proposal to solve Haskell's MPTC dilemma

2010-05-26 Thread Max Bolingbroke
Hi Carlos,

Apologies for the lateness of my reply.

On 23 May 2010 02:24, Carlos Camarao carlos.cama...@gmail.com wrote:
 I think that a notion of orphan instances based on whether an
 instance is defined or not in the module where the class of the
 instance is defined is not very nice

I broadly agree, but pragmatically the notion of orphans is useful for
designing robust libraries, even if the notion is a bit horrible.

 A benefit of adopting our approach would be that defaulting would
 become unnecessary (defaulting always occurring in favor of visible
 definitions).

This is something I don't understand (and is not elaborated in your
paper that I can see). Defaulting seems like an orthogonal mechanism.
It turns a constraint that really does have multiple solutions (e.g.
(Num a) = ...) into one where a particular preferred choice is taken
(e.g. Num Int), in situations where abstracting over the choice is
disallowed.

However, you mechanism only turns constraints into instances when
there is no ambiguity.

Can you perhaps explain what you mean a bit further?

I looked at your definition for orphan-hood, which I think might be OK
if you don't have FlexibleInstances. However, if you do then consider
this series of modules:


{-# LANGUAGE MultiParamTypeClasses #-}
module Common where

class C a b where
foo :: a - b - String



{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}
{-# OPTIONS_GHC -fwarn-orphans #-}
module Mod2 where

import Common

data E = E

instance C a E where
foo _ _ = Mod2



{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}
{-# OPTIONS_GHC -fwarn-orphans #-}
module Mod1 where

import Common

data D = D

instance C D b where
foo _ _ = Mod1



{-# OPTIONS_GHC -fwarn-orphans #-}
import Common
import Mod1
import Mod2

main = putStrLn (foo D E)


None of the instances are reported as orphans but IMHO they should be,
because we get a conflict in the Main module. I guess that a MPTC
instance (C t1 .. tn) for class C in module M1 is NOT an orphan if:
 1) C is defined in the same module as the instance
 2) OR ALL the t1..tn are instantiated to some concrete type (i.e. not
a type variable) defined in the same module as the instance

Imagine that we had an instance defined in a different module than the
class and violating 2). Then:

\exists i. t_i is a type variable or a datatype defined in another module

Case 1: If t_i is a type variable, we can have a parallel module M2:


data F = F

instance C a_1 ... a_{i-1} F a_{i+1} ... a_n where


Adding the instance to M2 may break client code because it is
potentially ambiguous with the one from M1. Furthermore, the instance
is considered non-orphan by GHC because it has at least one type which
is defined in the same module. However, at least one of this instance
and the one in M1 should have been flagged as orphans :(

Case 2: if t_i is a datatype G defined in another module, we can
similarly consider adding a new instance to that module:


instance C a_1 ... a_{i-1} G a_{i+1} ... a_n where


Same argument as for case 1.

Does this seem right?

==

Basically, you want an orphanhood criteria P you can test locally on a
per-module basis such that:
 * For any composition of modules where P holds on every module individually...
 * Changing any module by *adding* instances such that P still holds..
 * Is guaranteed not to break any other module due to ambiguity

It is not clear to me exactly what this should look like, especially
in the presence of more complicated instance definitions (like the
instance C [Bool] style of thing allowed by FlexibleInstances. It
would probably be interesting to find out though.

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


[Haskell-cafe] yet another functional reactive programming tutorial :)

2010-05-26 Thread Jinjing Wang
Dear list,

As I'm learning frp and reading the wonderful tutorial at

http://www.formicite.com/dopage.php?frp/frp.html

, I'm putting up some more basic cheatsheet style tutorial for myself.

http://github.com/nfjinjing/frp-guide

Feel free to take advantage of it.

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


Re: [Haskell] Re: [Haskell-cafe] Work on Video Games in Haskell

2010-05-26 Thread Edward Kmett
On Wed, May 26, 2010 at 5:22 PM, Pierre-Etienne Meunier 
pierreetienne.meun...@gmail.com wrote:

 Well in this case I'd be really interested in seeing how the can tell the
 difference, be it only from a simple complexity theoretic point of view ! I
 understand they may look for common patterns in their compiler code to tell
 the difference between GHC's generated code and theirs, but pretending they
 can do it in this case only shows that Apple lawyers never communicate with
 the engineers.


I think it is more a matter of Jobs trying to find any way he could to
quickly block Adobe's attempted end-run around his blockade against Flash
apps.

While we can all acknowledge the technical impossibility of identifying the
original source language of a piece of code, all they need is to raise the
spectre of doubt, and they have practically gutted all concern of a cross
platform development environment emerging, because no sound business plan
can be built on I hope my major and only possible distributor doesn't
figure out what I'm doing!

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


Re: [Haskell-cafe] Re: Math questions

2010-05-26 Thread Dan Doel
On Wednesday 26 May 2010 5:38:57 pm Pete Chown wrote:
 test :: (Eq a) = (Int - a) - (Int - a) - Bool
 test f1 f2 = unsafePerformIO $ do
  goodSoFar - newIORef True
  forLoop 1 100 $ \i -
when (f1 i /= f2 i) $ writeIORef goodSoFar False
  readIORef goodSoFar

The problem with this algorithm is that it needlessly tests f1 against f2 for 
all i, even when a non-matching value has has already been found. Using the 
power of call-with-current-continuation, I have constructed an algorithm that 
lacks this deficiency:

import Control.Monad.Cont

test f g = flip runCont id . callCC $ \escape -
  do forM_ [1..100] $ \n -
   when (f n /= g n) $
 escape False
 return True

This should perform almost 75% less work in the testFunc1 case! It certainly 
feels much snappier.

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


[Haskell-cafe] Problem when installing gtk2hs.

2010-05-26 Thread Magicloud Magiclouds
Hi, I have met similar problem before, and I do not know what to do.

# cabal install --reinstall gtk2hs-buildtools
Resolving dependencies...
Configuring gtk2hs-buildtools-0.9...
cabal: alex is required but it could not be found.
cabal: Error: some packages failed to install:
gtk2hs-buildtools-0.9 failed during the configure step. The exception was:
ExitFailure 1
# alex -v
Alex version 2.3.3, (c) 2003 Chris Dornan and Simon Marlow
-- 
竹密岂妨流水过
山高哪阻野云飞
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Proposal to solve Haskell's MPTC dilemma

2010-05-26 Thread Isaac Dupree

On 05/26/10 15:42, Carlos Camarao wrote:

What do you think?


I think you are proposing using the current set of instances in scope in 
order to remove ambiguity.  Am I right?  ..I read the haskell-cafe 
thread so far, and it looks like I'm right.  This is what I'll add to 
what's been said so far:


Your proposal appears to allow /incoherent/ instance selection.  This 
means that an expression can be well-typed in one module, and well-typed 
in another module, but have different semantics in the two modules.  For 
example (drawing from above discussion) :


module C where
class F a b where f :: a - b
class O a where o :: a

module P where
import C
instance F Bool Bool where f = not
instance O Bool where o = True
k :: Bool
k = f o

module Q where
import C
instance F Int Bool where f = even
instance O Int where o = 0
k :: Bool
k = f o

module Main where
import P
import Q
-- (here, all four instances are in scope)
main = do { print P.k ; print Q.k }
-- should result, according to your proposal, in
-- False
-- True
-- , am I correct?

Also, in your paper, example 2 includes

m = (m1 * m2) * m3

and you state

In Example 2, there is no means of specializing type variable c0 occurring in 
the
type of m to Matrix.


I suggest that there is an appropriate such means, namely, to write
m = (m1 * m2 :: Matrix) * m3
.  (Could the paper address how that solution falls short?  Are there 
other cases in which there is more than just a little syntactical 
convenience at stake?, or is even that much added code too much for some 
use-case?)


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


Re: [Haskell] Re: [Haskell-cafe] Work on Video Games in Haskell

2010-05-26 Thread Ben Lippmeier

On 27/05/2010, at 9:01 AM, Edward Kmett wrote:
 While we can all acknowledge the technical impossibility of identifying the 
 original source language of a piece of code...


Uh,

desire:tmp benl$ cat Hello.hs
main = putStr Hello

desire:tmp benl$ ghc --make Hello.hs

desire:tmp benl$ strings Hello | head
Hello
base:GHC.Arr.STArray
base:GHC.Arr.STArray
base:GHC.Classes.D:Eq
base:GHC.Classes.D:Eq
failed to read siginfo_t
 failed: 
Warning: 
select
buildFdSets: file descriptor out of range

...




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


Re: [Haskell] Re: [Haskell-cafe] Work on Video Games in Haskell

2010-05-26 Thread Daniel Peebles
Next up, binary obfuscation! Apple already uses these extensively in their
Fairplay code. Surely it isn't against the rules (yet?) to apply them to
your program before submitting it to the store? :P

On Wed, May 26, 2010 at 11:01 PM, Ben Lippmeier b...@ouroborus.net wrote:


 On 27/05/2010, at 9:01 AM, Edward Kmett wrote:
  While we can all acknowledge the technical impossibility of identifying
 the original source language of a piece of code...


 Uh,

 desire:tmp benl$ cat Hello.hs
 main = putStr Hello

 desire:tmp benl$ ghc --make Hello.hs

 desire:tmp benl$ strings Hello | head
 Hello
 base:GHC.Arr.STArray
 base:GHC.Arr.STArray
 base:GHC.Classes.D:Eq
 base:GHC.Classes.D:Eq
 failed to read siginfo_t
  failed:
 Warning:
 select
 buildFdSets: file descriptor out of range

 ...




 ___
 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] Re: [Haskell-cafe] Work on Video Games in Haskell

2010-05-26 Thread Ben Lippmeier

Objects in the heap also have a very regular structure. They all have code 
pointers as their first word, which point to info tables that also have a 
regular structure [1]. GHC produced code is probably one of the easiest to 
identify out of all compiled languages...

http://hackage.haskell.org/trac/ghc/wiki/Commentary/Rts/Storage/HeapObjects

Ben.


On 27/05/2010, at 1:15 PM, Daniel Peebles wrote:

 Next up, binary obfuscation! Apple already uses these extensively in their 
 Fairplay code. Surely it isn't against the rules (yet?) to apply them to your 
 program before submitting it to the store? :P
 
 On Wed, May 26, 2010 at 11:01 PM, Ben Lippmeier b...@ouroborus.net wrote:
 
 On 27/05/2010, at 9:01 AM, Edward Kmett wrote:
  While we can all acknowledge the technical impossibility of identifying the 
  original source language of a piece of code...
 
 
 Uh,
 
 desire:tmp benl$ cat Hello.hs
 main = putStr Hello
 
 desire:tmp benl$ ghc --make Hello.hs
 
 desire:tmp benl$ strings Hello | head
 Hello
 base:GHC.Arr.STArray
 base:GHC.Arr.STArray
 base:GHC.Classes.D:Eq
 base:GHC.Classes.D:Eq
 failed to read siginfo_t
  failed:
 Warning:
 select
 buildFdSets: file descriptor out of range
 
 ...
 
 
 
 
 ___
 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] Re: [Haskell-cafe] Work on Video Games in Haskell

2010-05-26 Thread C. McCann
On Wed, May 26, 2010 at 11:01 PM, Ben Lippmeier b...@ouroborus.net wrote:
 While we can all acknowledge the technical impossibility of identifying the 
 original source language of a piece of code...


 Uh,

∀p (PieceOfCode(p) - CanIdentifySourceLanguage(p))

is clearly false, while

∃p (PieceOfCode(p) - CanIdentifySourceLanguage(p))

is clearly true.

Natural language does a rather poor job of making quantification unambiguous.

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


Re: [Haskell] Re: [Haskell-cafe] Work on Video Games in Haskell

2010-05-26 Thread Brandon S. Allbery KF8NH

On May 26, 2010, at 23:23 , C. McCann wrote:
On Wed, May 26, 2010 at 11:01 PM, Ben Lippmeier b...@ouroborus.net  
wrote:
While we can all acknowledge the technical impossibility of  
identifying the original source language of a piece of code...


Uh,


∀p (PieceOfCode(p) - CanIdentifySourceLanguage(p))
is clearly false, while
∃p (PieceOfCode(p) - CanIdentifySourceLanguage(p))
is clearly true.

Natural language does a rather poor job of making quantification  
unambiguous.



If you really want to get jiggy with the corner cases, ask what counts  
as a transformation.

/bin/cat?
sed 's/a/b/g'?
sed 'y/abcdefghijklmnopqrstuvwxyz/zyxwvutsrqponmlkjihgfedcba/'?
unlit?
cpp?

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell] Re: [Haskell-cafe] Work on Video Games in Haskell

2010-05-26 Thread Brandon S. Allbery KF8NH

On May 27, 2010, at 00:20 , Brandon S. Allbery KF8NH wrote:

On May 26, 2010, at 23:23 , C. McCann wrote:
On Wed, May 26, 2010 at 11:01 PM, Ben Lippmeier  
b...@ouroborus.net wrote:
While we can all acknowledge the technical impossibility of  
identifying the original source language of a piece of code...


Uh,


∀p (PieceOfCode(p) - CanIdentifySourceLanguage(p))
is clearly false, while
∃p (PieceOfCode(p) - CanIdentifySourceLanguage(p))
is clearly true.

Natural language does a rather poor job of making quantification  
unambiguous.


If you really want to get jiggy with the corner cases, ask what  
counts as a transformation.



And the best, if obsolescent, example of all:  cfront.

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe