Re: [Haskell-cafe] Research language vs. professional language

2008-09-02 Thread Manuel M T Chakravarty

Ryan Ingram:

On Sun, Aug 31, 2008 at 7:27 PM, Jonathan Cast
[EMAIL PROTECTED] wrote:

This concept of `day-to-day work' is a curious one.  Haskell is not a
mature language, and probably shouldn't ever be one.


I see where you are coming from here, but I think that train has
already started and can't be stopped.  I find Haskell interesting as a
professional programmer for these four reasons: it's pure, it's
functional, it's lazy, and it's got a great compiler.

[..]
There will always be new discoveries in purely functional  
programming,

and as the art advances, features like this ad-hoc overloading hack
(and ACIO) will become obsolete and have to be thrown over-board.


This is a good point.  However, it seems to me that the pure
programming language research is moving towards dependently typed
languages, and that progress in Haskell has been more
application-side; transactional memory and data-parallel, along with
research on various fusion techniques, for example.


Let me quote from the Preface of the Haskell report:

It was decided that a committee should be formed to design such a  
language, providing faster communication of new ideas, a stable  
foundation for real applications development, and a vehicle through  
which others would be encouraged to use functional languages.


and

It should be suitable for teaching, research, and applications,  
including building large systems.


From the outset, the Haskell vision included being a stable  
foundation for real applications development (I read this as aiming  
at industrial use) and research.  This leads to tension, but, for  
better or worse, I believe that the Haskell community -in its current  
form- is pretty much committed to meet both goals.  You can see it in  
GHC.  It implements the static Haskell 98 and at the same time many  
experimental, researchy features (which you use at your own risk).   
More generally, I think that this is one of the killer features of  
functional languages, they provide a fast path from innovative, even  
highly theoretical research to practical applications.


This may not work forever -maybe all interesting research that can be  
done in Haskell without radical changes will have been done at some  
point- but for the moment, I think we are in pretty good shape.


Manuel

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


Re: [Haskell-cafe] Re: [Haskell] Top Level -

2008-09-02 Thread Adrian Hey

Ganesh Sittampalam wrote:
You see this as a requirement that can be discharged by adding the ACIO 
concept; I see it as a requirement that should be communicated in the type.


Another way of looking at it is that Data.Unique has associated with it 
some context in which Unique values are safely comparable. You want that 
context to always be the top-level/RTS scope, I would like the defining 
that context to be part of the API.


But why pick on Data.Unique as special? Because I just happened to have
pointed out it uses a global variable? If you didn't know this I
suspect this issue just wouldn't be an issue at all. Why haven't you
raised a ticket complaining about it's API having the wrong type
sigs? :-)

There's shed loads of information and semantic subtleties about pretty
much any operation you care to think of in the IO monad that isn't
communicated by it's type. All you know for sure is that it's weird,
because if it wasn't it wouldn't be in the IO monad.

So I think you're applying double standards.


We have to have something concrete to discuss and this is the simplest.
Like I said there are a dozen or so other examples in the base package
last time I counted


Would you mind listing them? It might help provide some clarity to the 
discussion.


Here's what you can't find in the libs distributed with ghc. Note this
does not include all uses of unsafePerformIO. It only includes uses
to make a global variable.

Control.Concurrent   1
Control.OldException 1
Data.HashTable   1
Data.Typeable1
Data.Unique  1
GHC.Conc 8
GHC.Handle   3
System.Random1
Language.Haskell.Syntax  1
System.Posix.Signals 2
System.Win32.Types   1
Network.BSD  1
System.Posix.User1
Total:  23

In the ghc source you can find 16 uses of the GLOBAL_VAR macro (can't
imagine what that does :-).

I didn't even attempt to figure out how global variables might be the
rts source. Anyone care to hazard a guess?

You can find a few more in the extra libs..
Graphics.UI.GLUT.Menu1
Graphics.UI.GLUT.Callbacks.Registration  3
Graphics.Rendering.OpenGL.GLU.ErrorsInternal 1
Total:   5

A few more:
wxHaskell 6
c2hs  1
GTK2HS1
SDL   0 !!

However, I happen to know that SDL suffers from the initialisation
issue and IIRC it needs at least 1 global to stop user using an unsafe
(possibly segfault inducing) calling sequence.

Anyway, that's all from me because I'm bored with this thread now.

Regards
--
Adrian hey


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


RE: [Haskell-cafe] Top Level -

2008-09-02 Thread Sittampalam, Ganesh
John Meacham wrote:
On Fri, Aug 29, 2008 at 04:33:50PM -0700, Dan Weston wrote:

 C++ faced this very issue by saying that with global data,
 uniqueness of initialization is guaranteed but order of
 evaluation is not. Assuming that the global data are 
 merely thunk wrappers over some common data source, this 
 means that at minimum, there can be no data dependencies 
 between plugins where the order of evaluation matters.

 Fortunately, we can do a whole lot better with haskell, the 
 type system guarentees that order of evaluation is irrelevant
 :) no need to specify anything about implementations.

Can't you write two recursive modules with - that depend on
each other, so that there's no valid initialisation order?

Contrived example follows:

module Module1 where

glob1 :: IORef Int
glob1 - mod2 = newIORef 

mod1 :: IO Int
mod1 = readIORef glob1

module Module2 where

glob2 :: IORef Int
glob2 - mod1 = newIORef 

mod2 :: IO Int
mod2 = readIORef glob2

It might need some strictness annotations to actually cause
non-termination at initialisation rather than just make the results
of mod1 and mod2 be _|_.

I think those initialisers do satisfy ACIO, though I'm not certain -
from the point of view of dataflow, you can certainly remove them
both together if the rest of the code doesn't use mod1 or mod2, and
likewise they commute with any other IO operations. But on the other
hand there's no way to actually put them in an order that doesn't
cause non-termination.

Cheers,

Ganesh


==
Please access the attached hyperlink for an important electronic communications 
disclaimer: 

http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html
==

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


Re: [Haskell-cafe] Top Level -

2008-09-02 Thread Adrian Hey

Sittampalam, Ganesh wrote:

Can't you write two recursive modules with - that depend on
each other, so that there's no valid initialisation order?

Contrived example follows:

module Module1 where

glob1 :: IORef Int
glob1 - mod2 = newIORef 


mod1 :: IO Int
mod1 = readIORef glob1

module Module2 where

glob2 :: IORef Int
glob2 - mod1 = newIORef 


mod2 :: IO Int
mod2 = readIORef glob2


Immediatly breaking my promise to shut up..

This is illegal because you're only allowed to use ACIO in top level -
bindings and readIORef isn't (and clearly could not be) ACIO.

Regards
--
Adrian Hey

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


RE: [Haskell-cafe] Top Level -

2008-09-02 Thread Sittampalam, Ganesh
  Contrived example follows:
 
  module Module1 (mod1) where
  import Module2
 
  glob1 :: IORef Int
  glob1 - mod2 = newIORef
 
  mod1 :: IO Int
  mod1 = readIORef glob1
 
  module Module2 (mod2) where

  import Module1

  glob2 :: IORef Int
  glob2 - mod1 = newIORef
 
  mod2 :: IO Int
  mod2 = readIORef glob2

 This is illegal because you're only allowed to use ACIO
 in top level - bindings and readIORef isn't (and clearly
 could not be) ACIO.

(made a couple of changes to quoted example; added import
statements and explicit export lists)

Even though I never call writeIORef on glob1 or glob2, and
can change the example as above so we don't export them, so
it's impossible to ever do so?

As an alternative, consider

module Module1 (mod1) where
import Module2

glob1 :: Int
glob1 - return $! mod2

mod1 :: Int
mod1 = glob1
 
module Module2 (mod2) where

import Module1

glob2 :: Int
glob2 - return $! mod1
 
mod2 :: Int
mod2 = glob2

Even more artificial, of course.

Arguably both of these cases are not ACIO simply because
of the non-termination effects, but it's not obvious to
me how you tell just by looking at either one's code together
with the declared API of the other. Is anything strict
automatically forbidden by ACIO?

Cheers,

Ganesh




==
Please access the attached hyperlink for an important electronic communications 
disclaimer: 

http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html
==

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


[Haskell-cafe] Re: [Haskell] Top Level -

2008-09-02 Thread Ashley Yakeley

Ganesh Sittampalam wrote:
I have a feeling it might be non-trivial; the dynamically loaded bit of 
code will need a separate copy of the module in question, since it might 
be loaded into something where the module is not already present.


Already the dynamic loader must load the module into the same address 
space and GC, i.e. the same runtime. So it should be able to make sure 
only one copy gets loaded.


What is the status of dynamic loading in Haskell? What does hs-plugins 
do currently?


Well, the safety of - being run twice in the Data.Unique case is based 
around the two different Data.Unique types not being compatible.


Right. The only code that can construct Unique values is internal to 
Data.Unique.


Let's 
suppose some other module uses a -, but returns things based on that - 
that are some standard type, rather than a type it defines itself. Is 
module duplication still safe?


In this case, duplicate modules of different versions is as safe as 
different modules. In other words, this situation:


  mypackage-1.0 that uses -
  mypackage-2.0 that uses -

is just as safe as this situation:

  mypackage-1.0 that uses -
  otherpackage-1.0 that uses -

The multiple versions issue doesn't add any problems.

Well, let me put it this way; since I don't like -, and I don't 
particularly mind Typeable, I wouldn't accept IOWitness as an example of 
something that requires - to implement correctly, because I don't see 
any compelling feature that you can only implement with -.


Why don't you like -? Surely I've addressed all the issues you raise? 
Multiple package versions does not actually cause any problems. 
Capabilities would be really nice, but the right approach for that is to 
create a new execution monad. There is an obligation regarding dynamic 
loading, but it looks like dynamic loading might need work anyway.


Since this is a matter of aesthetics, I imagine it will end with a list 
of pros and cons.


There's some unsafety somewhere in both Typeable and IOWitnesses, and in 
both cases it can be completely hidden from the user - with Typeable, 
just don't let the user define the typeOf function at all themselves. 


It's worse than that. If you derive an instance of Typeable for your 
type, it means everyone else can peer into your constructor functions 
and other internals. Sure, it's not unsafe, but it sure is ugly.


Sometimes you want to do witness equality tests rather than type 
equality tests. For instance, I might have a foo exception and a 
bar exception, both of which carry an Int. Rather than create new 
Foo and Bar types, I can just create a new witness for each.


This is precisely what newtype is designed for, IMO. We don't need 
another mechanism to handle it.


It's not what newtype is designed for. Newtype is designed to create 
usefully new types. Here, we're only creating different dummy types so 
that we can have different TypeRep values, which act as witnesses. It's 
the TypeReps that actually do the work.


It would be much cleaner to declare the witnesses directly.

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


[Haskell-cafe] Re: [Haskell] The initial view on typed sprintf and sscanf

2008-09-02 Thread ChrisK

Matthew Brecknell wrote:

Unfortunately, I don't seem to be able to make the expected fprintf
function, because printf's format-dependent parameter list makes it
impossible to find a place to pass the handle. Hence the C++-like ()
ugliness.



How about this:

fprintf :: Handle - F (IO ()) b - 
fprintf h fmt = write fmt id  where

  write :: F a b - (IO () - a) - b
  write (FLit str) k = k (hPutStr h str)
  write FInt k = \i - k (hPutStr h (show i))
  write FChr k = \c - k (hPutChar h c)
  write (FPP (PrinterParser pr _)) k = \x - k (hPutStr h (pr x))
  write (a :^ b)  k = write a (\sa - write b (\sb - k (sa  sb)))


*PrintScan fprintf stdout fmt5 15 1.3 '!'
abc15cde1.3!*PrintScan

The first thing I did last night was change String to
type ShowS = String - String :


intps :: F a b - (ShowS - a) - b
intps (FLit str) k = k (str++)
intps FInt   k = \x - k (shows x)
intps FChr   k = \x - k (x:)
intps (FPP (PrinterParser pr _))  k = \x - k (pr x ++)
intps (a :^ b)   k = intps a (\sa - intps b (\sb - k (sa . sb)))



sprintfs :: F ShowS b - b
sprintfs fmt = intps fmt id


Ideally PrinterParser would display using ShowS as well:


data PrinterParser a
  = PrinterParser (a - ShowS) (String - Maybe (a, String))


Or one could use instance witnesses via GADTs to wrap up Show:


data F a b where
FSR  :: (Show b,Read b) = F a (b - a)


But I think changing PrinterParser would result in simpler code.

Cheers,
  Chris

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


[Haskell-cafe] REMINDER: OpenSPARC project application deadline this Friday

2008-09-02 Thread Duncan Coutts

 http://haskell.org/opensparc/

The deadline for applications for the Haskell OpenSPARC project is
rapidly approaching. Applications have to be sent to:

 [EMAIL PROTECTED]

by the end of this week, Friday the 5th September.

If you want any comments on your application before you submit it then
contact me directly.

Duncan
(project coordinator)



In other news, the server that Sun Microsystems donated to the community
has just gone online at Chalmers:

http://blog.well-typed.com/2008/09/the-new-haskellorg-community-sparc-server-is-online/

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


Re: [Haskell-cafe] It's not a monad - what is it? looking for nice syntactic sugar, customizable do notation?

2008-09-02 Thread Yitzchak Gale
Marc Weber wrote:
 (3) Third idea:
  xmlWithInnerIO - execXmlT $ do
xmlns http://www.w3.org/1999/xhtml;  lang en-US  xml:lang en-US
head $ title $ text minimal
body $ do
  args - lift $ getArgs
  h1 $ text minimal
  div $ text $ args passed to this program:  ++ (show args)
 I still think that (3) would be superiour..
 Is there a way to define my own = and  functions such as:

There is also the combinator approach of Text.Html, which
gives you a syntax similar to (3) but without abusing do:

(rootElt ! [xmlns http://www.w3.org/1999/xhtml;,
   lang en-US  xml:lang en-US]) $ concatXml
  [head $ title $ text minimal
  ,body $ concatXml
[h1 $ text minimal
,div $ text $ args passed to this program:  ++ (show args)
]
  ]

You use concatXml (it's concatHtml in the library) followed
by a list, instead of do, for nesting.

(Also, it's stringToHtml instead of text in the library.)

A few more brackets, but still pretty clean. Also, you'll have
pass in your args from somewhere else, in the IO monad -
which is probably a better design anyway.

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


Re: [Haskell-cafe] It's not a monad - what is it? looking for nice syntactic sugar, customizable do notation?

2008-09-02 Thread Yitzchak Gale
Oops, needed to convert one more  into a comma:

(rootElt ! [xmlns http://www.w3.org/1999/xhtml;
 ,lang en-US
 ,xml_lang en-US
 ]) $ concatXml

etc.

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


[haskell-cafe] Monad and kinds

2008-09-02 Thread Ramin
Hello, I'm new here, but in the short time I have known Haskell, I can 
already say it's my favorite computer language.


Except for monads, and no matter how many tutorials I read, I find the 
only kind of monad I can write is the monad that I copied and pasted 
from the tutorial, i.e. I still don't get it even though I thought I 
understood the tutorial, and I'm stuck using monads others have already 
written.


My project is this: I am writing a mini-database of sorts. I thought I 
would make a query a monad, so I could chain multiple queries together 
using the do notation, and run more complex queries on the list in one 
shot. The query itself is stateful because it contains information that 
changes as the database is traversed. The query may also make updates to 
the records. I got the program to work perfectly using purely functional 
techniques, but complex queries resulted in that stair-step looking 
code. So I thought this would be the perfect opportunity to try my hand 
at monads.


The query monad I wrote looks something like this (much simplified):
   data Query state rec = Query !(state, rec)

Where state is the type of state, so a query can contain any 
information relevant to the search and can be updated as the search 
progresses.
Then, rec is the type of records in the database, which isn't 
determined inside the database module, so I can't just declare rec to 
be of any type I choose.


But I just cannot write the instance declaration for my Query data type 
no matter what I try. If I write:

   instance Monad Query where
   return (initState, someRecord) = Query (initState, someRecord)
   {- code for (=) -}
GHC gives an error, Expected kind `* - *', but `Scanlist_ctrl' has 
kind `* - * - *' . If I try this:

   instance Monad (Query state) where
   return (initState, someRecord) = Query (initState, someRecord)
   {- code for (=) -}
GHC give an error, Occurs check: cannot construct the infinite type: a 
= (s, a) when trying to generalise the type inferred for `return' .


I get the sense I am trying to shove a square peg into a round hole. I 
was thinking of trying some other things, like implementing the monad in 
a higher-level module where I knew the type of the records I would be 
using, but I don't like being told where to implement things. I also 
thought of trying to re-write my query algorithm to somehow use 
Control.Monad.State.Strict instead of my own query type, but then I 
wouldn't get to write my own monad!


Though the information given in this e-mail is limited, is there anyone 
who can clearly see there is something about monads that I just don't 
get and tell me what it is?


Anyone who took the time to read this, I am very appreciative.
   Ramin Honary
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [haskell-cafe] Monad and kinds

2008-09-02 Thread Jake Mcarthur

On Sep 2, 2008, at 8:34 AM, Ramin wrote:


  instance Monad Query where
  return (initState, someRecord) = Query (initState, someRecord)
  {- code for (=) -}
GHC gives an error, Expected kind `* - *', but `Scanlist_ctrl' has  
kind `* - * - *' .


I believe you understand the problem with the above code, judging from  
your attempt to fix it below.



If I try this:
  instance Monad (Query state) where
  return (initState, someRecord) = Query (initState, someRecord)
  {- code for (=) -}
GHC give an error, Occurs check: cannot construct the infinite  
type: a = (s, a) when trying to generalise the type inferred for  
`return' .


The problem is your type for the return function. The way you have  
written it, it would be `return :: (state, rec) - Query state rec`.  
Perhaps it would be easier to see the problem if we defined `type M =  
Query MyState`. Then you have `return :: (MyState, rec) - M rec`.  
Compare this to the type it must be unified with: `return :: a - m  
a`. The two 'a's don't match! The type you are after is actually  
`return :: rec - M rec` or `return :: rec - Query state rec`.


I hope this helps lead you in the right direction. I'm not giving you  
the solution because it sounds like you want to solve this for  
yourself and learn from it.


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


[Haskell-cafe] ICFP09 Announcement

2008-09-02 Thread Matthew Fluet (ICFP Publicity Chair)
++

 ANNOUNCEMENT

  The 14th ACM SIGPLAN International
 Conference on Functional Programming

  ICFP 2009

   31st August - 2nd September 2009
  Edinburgh, United Kingdom

ICFP provides a forum for researchers and developers to hear about the
latest work  on the design,  implementations, principles, and  uses of
functional programming.  ICFP 2009 will be held in Scotland's historic
capital  city of  Edinburgh, during  the final  week of  the Edinburgh
International  Festival.   Further   information  is  available  from:
http://www.cs.nott.ac.uk/~gmh/icfp09.html

Graham Hutton
General Chair, ICFP 2009

++
| Dr Graham HuttonEmail : [EMAIL PROTECTED]  |
| Functional Programming Lab |
| School of Computer Science  Web   : www.cs.nott.ac.uk/~gmh |
| University of Nottingham   |
| Jubilee Campus, Wollaton Road   Phone : +44 (0)115 951 4220|
| Nottingham NG8 1BB, UK |
++
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [haskell-cafe] Monad and kinds

2008-09-02 Thread Daniel Fischer
Am Dienstag, 2. September 2008 15:34 schrieb Ramin:
 Hello, I'm new here, but in the short time I have known Haskell, I can
 already say it's my favorite computer language.

 Except for monads, and no matter how many tutorials I read, I find the
 only kind of monad I can write is the monad that I copied and pasted
 from the tutorial, i.e. I still don't get it even though I thought I
 understood the tutorial, and I'm stuck using monads others have already
 written.

Considering some pretty brilliant people have a few years advantage over you, 
don't expect to find a situation where you need a monad not yet written for a 
while :)


 My project is this: I am writing a mini-database of sorts. I thought I
 would make a query a monad, so I could chain multiple queries together
 using the do notation, and run more complex queries on the list in one
 shot. The query itself is stateful because it contains information that
 changes as the database is traversed. The query may also make updates to
 the records. I got the program to work perfectly using purely functional
 techniques, but complex queries resulted in that stair-step looking
 code. So I thought this would be the perfect opportunity to try my hand
 at monads.

 The query monad I wrote looks something like this (much simplified):
 data Query state rec = Query !(state, rec)

 Where state is the type of state, so a query can contain any
 information relevant to the search and can be updated as the search
 progresses.
 Then, rec is the type of records in the database, which isn't
 determined inside the database module, so I can't just declare rec to
 be of any type I choose.

 But I just cannot write the instance declaration for my Query data type
 no matter what I try. If I write:
 instance Monad Query where
 return (initState, someRecord) = Query (initState, someRecord)
 {- code for (=) -}
 GHC gives an error, Expected kind `* - *', but `Scanlist_ctrl' has
 kind `* - * - *' . If I try this:
 instance Monad (Query state) where
 return (initState, someRecord) = Query (initState, someRecord)
 {- code for (=) -}
 GHC give an error, Occurs check: cannot construct the infinite type: a
 = (s, a) when trying to generalise the type inferred for `return' .

The type of return is (Monad m = a - m a). If m = (Query state), the type of 
return becomes (rec - Query state rec) and (return a) must be 
Query (something of type state, a).
Now, if you try
return (initState, someRecord) = Query (initState, someRecord),
the (initState, someRecord) on the left has type a, and the someRecord on the 
right has the same type. From the left hand side follows a = (state, rec), 
hence someRecord has type rec. But from the right hand side, someRecord must 
have type a = (state, rec), so we find rec = (state, rec). That of course is 
impossible.


 I get the sense I am trying to shove a square peg into a round hole. I
 was thinking of trying some other things, like implementing the monad in
 a higher-level module where I knew the type of the records I would be
 using, but I don't like being told where to implement things. I also
 thought of trying to re-write my query algorithm to somehow use
 Control.Monad.State.Strict instead of my own query type, but then I
 wouldn't get to write my own monad!

But this looks very much like an application well suited for the State monad 
(or a StateT). So why not use that? Or you could write your own specialised 
version without looking at the existing code, so you could at least 
familiarise yourself a little more with monads.

 Though the information given in this e-mail is limited, is there anyone
 who can clearly see there is something about monads that I just don't
 get and tell me what it is?

 Anyone who took the time to read this, I am very appreciative.
 Ramin Honary

A monad is a type constructor of kind (* - *), that is, it takes one type as 
argument and returns some other type. Your Query takes two types as argument 
and makes one new type from that, so Query has kind (* - * - *) and cannot 
possibly be a monad. What could be a monad is (Query a) which has kind (* - 
*). However, the only halfway meaningful return you can define then is
return someRecord = Query (undefined, someRecord),
which doesn't look particularly useful. And (=) then can't make use of the 
state either, it would have to be one of
Query (s,r) = f = f r
or
Query (s,r) = f = let Query (_,r1) = f r in Query (s,r1)
or something completely meaningless.

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


Re: [Haskell-cafe] Top Level -

2008-09-02 Thread David Roundy
On Tue, Sep 02, 2008 at 10:10:31AM +0100, Sittampalam, Ganesh wrote:
   Contrived example follows:
  
   module Module1 (mod1) where
   import Module2
  
   glob1 :: IORef Int
   glob1 - mod2 = newIORef
  
   mod1 :: IO Int
   mod1 = readIORef glob1
  
   module Module2 (mod2) where
 
   import Module1
 
   glob2 :: IORef Int
   glob2 - mod1 = newIORef
  
   mod2 :: IO Int
   mod2 = readIORef glob2
 
  This is illegal because you're only allowed to use ACIO
  in top level - bindings and readIORef isn't (and clearly
  could not be) ACIO.
 
 (made a couple of changes to quoted example; added import
 statements and explicit export lists)
 
 Even though I never call writeIORef on glob1 or glob2, and
 can change the example as above so we don't export them, so
 it's impossible to ever do so?
 
 As an alternative, consider
 
 module Module1 (mod1) where
 import Module2
 
 glob1 :: Int
 glob1 - return $! mod2
 
 mod1 :: Int
 mod1 = glob1
  
 module Module2 (mod2) where
 
 import Module1
 
 glob2 :: Int
 glob2 - return $! mod1
  
 mod2 :: Int
 mod2 = glob2
 
 Even more artificial, of course.
 
 Arguably both of these cases are not ACIO simply because
 of the non-termination effects, but it's not obvious to
 me how you tell just by looking at either one's code together
 with the declared API of the other. Is anything strict
 automatically forbidden by ACIO?

Isn't this just a pure infinite loop? Why is it a problem that ACIO
allows you the flexibility that's present in any pure code?

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


RE: [Haskell-cafe] Top Level -

2008-09-02 Thread Sittampalam, Ganesh
 
David Roundy wrote:
 On Tue, Sep 02, 2008 at 10:10:31AM +0100, Sittampalam, Ganesh wrote:

 Arguably both of these cases are not ACIO simply because of the 
 non-termination effects, but it's not obvious to me how you tell just

 by looking at either one's code together with the declared API of the

 other. Is anything strict automatically forbidden by ACIO?

 Isn't this just a pure infinite loop? Why is it a problem that ACIO
 allows you the flexibility that's present in any pure code?

ACIO promises that you can remove anything unused without changing
the behaviour.

The same problem doesn't arise in pure code because you can't write
top-level strict bindings. The GHC extension to have strict bindings
(bang patterns) is explicitly disallowed at top-level:
http://www.haskell.org/ghc/docs/latest/html/users_guide/bang-patterns.ht
ml

Ganesh

==
Please access the attached hyperlink for an important electronic communications 
disclaimer: 

http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html
==

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


[Haskell-cafe] Re: [Haskell] Top Level -

2008-09-02 Thread Ganesh Sittampalam

On Tue, 2 Sep 2008, Ashley Yakeley wrote:


Ganesh Sittampalam wrote:
I have a feeling it might be non-trivial; the dynamically loaded bit of 
code will need a separate copy of the module in question, since it might be 
loaded into something where the module is not already present.


Already the dynamic loader must load the module into the same address 
space and GC, i.e. the same runtime. So it should be able to make sure 
only one copy gets loaded.


I don't think it's that easy, modules aren't compiled independently of 
each other, and there are lots of cross-module optimisations and so on.


What is the status of dynamic loading in Haskell? What does hs-plugins 
do currently?


I don't know for sure, but I think it would load it twice.

In any case, what I'm trying to establish below is that it should be a 
safety property of - that the entire module (or perhaps mutually 
recursive groups of them?) can be duplicated safely - with a new name, or 
as if with a new name - and references to it randomly rewritten to the 
duplicate, as long as the result still type checks. If that's the case, 
then it doesn't matter whether hs-plugins loads it twice or not.


Let's suppose some other module uses a -, but returns things based on that 
- that are some standard type, rather than a type it defines itself. Is 
module duplication still safe?


In this case, duplicate modules of different versions is as safe as 
different modules. In other words, this situation:


 mypackage-1.0 that uses -
 mypackage-2.0 that uses -

is just as safe as this situation:

 mypackage-1.0 that uses -
 otherpackage-1.0 that uses -

The multiple versions issue doesn't add any problems.


Agreed - and I further claim that duplicating the entire module itself 
can't cause any problems.


Well, let me put it this way; since I don't like -, and I don't 
particularly mind Typeable, I wouldn't accept IOWitness as an example of 
something that requires - to implement correctly, because I don't see any 
compelling feature that you can only implement with -.


Why don't you like -? Surely I've addressed all the issues you raise?


I'm still not happy that the current specification is good enough, 
although I think this thread is getting closer to something that might 
work.


Even with a good specification for -, I would rather see the need for 
once-only state reflected in the type of things that have such a need.


There is an obligation regarding dynamic loading, but it looks like 
dynamic loading might need work anyway.


I think the obligation should be on -, and the obligation is the 
duplication rule I proposed above.


Since this is a matter of aesthetics, I imagine it will end with a list of 
pros and cons.


Agreed.

There's some unsafety somewhere in both Typeable and IOWitnesses, and in 
both cases it can be completely hidden from the user - with Typeable, just 
don't let the user define the typeOf function at all themselves. 


It's worse than that. If you derive an instance of Typeable for your 
type, it means everyone else can peer into your constructor functions 
and other internals. Sure, it's not unsafe, but it sure is ugly.


True. I would argue that this is better solved with a better typeclass 
hierarchy (e.g. one class to supply a witness-style representation that 
only supports equality, then the typereps on top of that if you want 
introspection too).


Sometimes you want to do witness equality tests rather than type equality 
tests. For instance, I might have a foo exception and a bar exception, 
both of which carry an Int. Rather than create new Foo and Bar types, I 
can just create a new witness for each.


This is precisely what newtype is designed for, IMO. We don't need another 
mechanism to handle it.


It's not what newtype is designed for. Newtype is designed to create 
usefully new types. Here, we're only creating different dummy types so 
that we can have different TypeRep values, which act as witnesses. It's 
the TypeReps that actually do the work.


newtype is frequently used to create something that you can make a 
separate set of typeclass instances for. This is no different. You can 
argue that this use of newtype is wrong, but there's no point in 
just providing an alternative in one specific case.


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


Re: [Haskell-cafe] Re: [Haskell] Top Level -

2008-09-02 Thread Ganesh Sittampalam

On Tue, 2 Sep 2008, Adrian Hey wrote:


Ganesh Sittampalam wrote:
You see this as a requirement that can be discharged by adding the ACIO 
concept; I see it as a requirement that should be communicated in the type.


Another way of looking at it is that Data.Unique has associated with it 
some context in which Unique values are safely comparable. You want that 
context to always be the top-level/RTS scope, I would like the defining 
that context to be part of the API.


But why pick on Data.Unique as special? Because I just happened to have
pointed out it uses a global variable?


Only because I thought it was the running example.

If you didn't know this I suspect this issue just wouldn't be an issue 
at all. Why haven't you raised a ticket complaining about it's API 
having the wrong type sigs? :-)


Because I don't use it, and even if I did use it I would just live with 
the API it has.



There's shed loads of information and semantic subtleties about pretty
much any operation you care to think of in the IO monad that isn't
communicated by it's type. All you know for sure is that it's weird,
because if it wasn't it wouldn't be in the IO monad.


It does actually claim a specification, namely that no two calls to 
newUnique return values that compare equal.



We have to have something concrete to discuss and this is the simplest.
Like I said there are a dozen or so other examples in the base package
last time I counted


Would you mind listing them? It might help provide some clarity to the 
discussion.


Here's what you can't find in the libs distributed with ghc. Note this
does not include all uses of unsafePerformIO. It only includes uses
to make a global variable.


Thanks. It'd probably be a good addition to the wiki page on this topic 
for these to be catalogued in terms of why they are needed, though I'm 
(probably) not volunteering to do it :-)


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


[Haskell-cafe] What monad am I in?

2008-09-02 Thread Henry Laxen
Dear Group,

When I fire up ghci and define:

increment x = return (x+1)

I can say:
Main increment 1

and ghci dutifully replies 2. Also as expected, the type signature of 
increment is:  (Num a, Monad m) = a - m a

However, if I say:

Main let a = increment 1

I get:

interactive:1:8:
Ambiguous type variable `m' in the constraint:
  `Monad m' arising from a use of `increment' at interactive:1:8-18
Probable fix: add a type signature that fixes these type variable(s)


Have I, like Monsier Jourdain, been running in the IO monad all my
life, and didn't even know it?

Thanks,
Henry Laxen

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


Re: [Haskell-cafe] What monad am I in?

2008-09-02 Thread Jonathan Cast
On Tue, 2008-09-02 at 20:25 +, Henry Laxen wrote:
 Dear Group,
 
 When I fire up ghci and define:
 
 increment x = return (x+1)
 
 I can say:
 Main increment 1
 
 and ghci dutifully replies 2. Also as expected, the type signature of 
 increment is:  (Num a, Monad m) = a - m a
 
 However, if I say:
 
 Main let a = increment 1
 
 I get:
 
 interactive:1:8:
 Ambiguous type variable `m' in the constraint:
   `Monad m' arising from a use of `increment' at interactive:1:8-18
 Probable fix: add a type signature that fixes these type variable(s)
 
 
 Have I, like Monsier Jourdain, been running in the IO monad all my
 life, and didn't even know it?

Yes.  This is a peculiarity of GHCi (and ghc -e) --- IO actions at
top-level are executed by default, while non-IO values are simply
printed out.

jcc


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


Re: [Haskell-cafe] What monad am I in?

2008-09-02 Thread Marc Weber
 Have I, like Monsier Jourdain, been running in the IO monad all my
 life, and didn't even know it?
Sure, just try
readFile doesnotexist within ghci :-)
That's an IO action.
on the other side
ghci  (3+7)
10
is no IO action. So I think ghci has two default behaviours differing.
Either its a monad, than use IO, else evaluate the result. In both cases
show it. The ghc manual sould tell you all about this (too lazy to look
it up)


But the ghci error message is another one:
Try this:
 :set -XNoMonomorphismRestriction
 let increment x = return (x+1)
 let a = increment 1

the line let a = requires to find out about the type of m (Maybe any
Monad such as Maybe, list etc) without XNoMonomorphismRestriction.
With XNoMonomorphismRestriction you can tell ghc that you don't care yet
about this and it should try to resolve m later. That's why ghci shows
this:

ghci :t a
a :: (Num t, Monad m) = m t

The second way to get rid of the ghci error message is telling ghci
which monad you want:
increment 1 -- this works because it's run within IO
print $ increment 1 -- won't, because ghc does'n know about the m type
print $ fromJust $ increment 1 -- works again, because you tell ghc that m is 
Maybe here 
print $ (increment 1 :: [Int]) -- works as well, using list monad
...

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


Re: [Haskell-cafe] What monad am I in?

2008-09-02 Thread Ryan Ingram
ghci has some crazy defaulting rules for expressions at the top level.

In particular, it tries to unify those expressions with a few
different types, including IO.

On the other hand, the let-expression is typed like regular Haskell
and you run into the monomorphism restriction.

  -- ryan

On Tue, Sep 2, 2008 at 1:25 PM, Henry Laxen [EMAIL PROTECTED] wrote:
 Dear Group,

 When I fire up ghci and define:

 increment x = return (x+1)

 I can say:
 Main increment 1

 and ghci dutifully replies 2. Also as expected, the type signature of
 increment is:  (Num a, Monad m) = a - m a

 However, if I say:

 Main let a = increment 1

 I get:

 interactive:1:8:
Ambiguous type variable `m' in the constraint:
  `Monad m' arising from a use of `increment' at interactive:1:8-18
Probable fix: add a type signature that fixes these type variable(s)


 Have I, like Monsier Jourdain, been running in the IO monad all my
 life, and didn't even know it?

 Thanks,
 Henry Laxen

 ___
 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] joyent, solaris and ghc

2008-09-02 Thread Jason Dusek
  Is anyone on the list using GHC on Joyent's Solaris (x86_64)
  setup? If so, I would love to know whether it was easy/hard
  and what the process is.

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


Re: [Haskell-cafe] What monad am I in?

2008-09-02 Thread Philip Weaver
On Tue, Sep 2, 2008 at 5:33 PM, Ryan Ingram [EMAIL PROTECTED] wrote:

 ghci has some crazy defaulting rules for expressions at the top level.

 In particular, it tries to unify those expressions with a few
 different types, including IO.

 On the other hand, the let-expression is typed like regular Haskell
 and you run into the monomorphism restriction.


Right.  Just to make it clear for the original poster, this monomorphism
restriction is not about GHCi specifically, just GHC in general.  With the
-fno-monomorphism-restriction, you will not get this error.



  -- ryan

 On Tue, Sep 2, 2008 at 1:25 PM, Henry Laxen [EMAIL PROTECTED]
 wrote:
  Dear Group,
 
  When I fire up ghci and define:
 
  increment x = return (x+1)
 
  I can say:
  Main increment 1
 
  and ghci dutifully replies 2. Also as expected, the type signature of
  increment is:  (Num a, Monad m) = a - m a
 
  However, if I say:
 
  Main let a = increment 1
 
  I get:
 
  interactive:1:8:
 Ambiguous type variable `m' in the constraint:
   `Monad m' arising from a use of `increment' at interactive:1:8-18
 Probable fix: add a type signature that fixes these type variable(s)
 
 
  Have I, like Monsier Jourdain, been running in the IO monad all my
  life, and didn't even know it?
 
  Thanks,
  Henry Laxen
 
  ___
  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


[Haskell-cafe] Re: ANN: zip-archive 0.1

2008-09-02 Thread John MacFarlane
Thanks again for the feedback! I've modified the zip-archive library
along the lines you suggested. Version 0.1 is now available on
HackageDB.

John

+++ Duncan Coutts [Aug 26 08 21:36 ]:
 
 Generally it looks good, that the operations on the archive are mostly
 separated from IO of writing out archives or creating entries from disk
 files etc.
 
 Looking at the API there feels to be slightly too much exposed. Eg does
 the MSDOSDateTime need to be exposed, or the (de)compressData functions.
 
 My personal inclination is to leave off the Zip prefix in the names and
 use qualified imports. I'd also leave out trivial compositions like
 
 readZipArchive  f = toZipArchive $ B.readFile f
 writeZipArchive f = B.writeFile f . fromZipArchive
 
 but reasonable people disagree.
 
 For both the pack in my tar lib and your addFilesToZipArchive, there's a
 getDirectoryContentsRecursive function asking to get out. This function
 seems to come up often. Ideally pack/unpack and
 addFilesToZipArchive/extractFilesFromZipArchive would just be mapM_
 extract or create for an individual entry over the contents of the
 archive or the result of a recursive traversal.
 
 So yeah, I feel these operations ought to be simpler compositions of
 other things, in your lib and mine, since this bit is often the part
 where different use cases need slight variations, eg in how they write
 files, or deal with os-specific permissions/security stuff. So if these
 are compositions of simpler stuff it should be easier to add in extra
 stuff or replace bits.
 
 Duncan
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Arrow without `'

2008-09-02 Thread Peter Gavin

Valery V. Vorotyntsev wrote:

On 1/23/08, David Menendez [EMAIL PROTECTED] wrote:

On Jan 23, 2008 12:20 PM, Valery V. Vorotyntsev [EMAIL PROTECTED] wrote:

I've built GHC from darcs, and...
Could anybody tell me, what's the purpose of Arrow[1] not having `'
method?

It's derived from the Category superclass.


Yes, it is.

The right question: how to build `arrows' in such circumstances?

Here go 2 changes I made to `CoState.hs' accompanied by the
error messages. :) Unfortunately, I'm not arrow-capable enough to
make _proper_ changes to the code and satisfy GHC... Any help?



Well, without looking at your code, generally all you have to do is

1) move the definition of () to Category and rename it to (.) after flipping 
the arguments.

2) define the id method of Category which is just (arr id) or returnA.

So essentially

instance Arrow (Foo a) where
  a  b = compose a b
  pure f = ...
  first a = ...

becomes

instance Arrow (Foo a) where
  pure f = ...
  first a = ...

instance Category (Foo a) where
  id = arr id
  a . b = compose b a

That's it.  It's too bad there's no way to do this automatically in the 
libraries, but it could be noted in the API docs.


Pete


~~
Change #1:

$ darcs w Control/Arrow/Transformer/CoState.hs
What's new in Control/Arrow/Transformer/CoState.hs:

{
hunk ./Control/Arrow/Transformer/CoState.hs 23
+import Control.Category (())
}

--
Error #1:

Control/Arrow/Transformer/CoState.hs:29:7:
`' is not a (visible) method of class `Arrow'
Failed, modules loaded: Control.Arrow.Operations.

~~
Change #2:

$ darcs diff -u Control/Arrow/Transformer/CoState.hs
--- old-arrows/Control/Arrow/Transformer/CoState.hs 2008-01-24
14:54:29.852296559 +0200
+++ new-arrows/Control/Arrow/Transformer/CoState.hs 2008-01-24
14:54:29.852296559 +0200
@@ -20,12 +20,13 @@

 import Control.Arrow
 import Control.Arrow.Operations
+import Control.Category (())

  newtype CoStateArrow s a b c = CST (a (s - b) (s - c))

  instance Arrow a = Arrow (CoStateArrow s a) where
arr f = CST (arr (f .))
-   CST f  CST g = CST (f  g)
+-- CST f  CST g = CST (f  g)
first (CST f) = CST (arr unzipMap  first f  arr zipMap)

  zipMap :: (s - a, s - b) - (s - (a,b))

--
Error#2:

Control/Arrow/Transformer/CoState.hs:27:0:
Could not deduce (Control.Category.Category (CoStateArrow s a))
  from the context (Arrow a)
  arising from the superclasses of an instance declaration
   at Control/Arrow/Transformer/CoState.hs:27:0
Possible fix:
  add (Control.Category.Category
 (CoStateArrow s a)) to the context of
the instance declaration
  or add an instance declaration for
 (Control.Category.Category (CoStateArrow s a))
In the instance declaration for `Arrow (CoStateArrow s a)'
Failed, modules loaded: Control.Arrow.Operations.

Thank you.



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


Re: [Haskell-cafe] Re: ANN: zip-archive 0.1

2008-09-02 Thread Don Stewart
jgm:
 Thanks again for the feedback! I've modified the zip-archive library
 along the lines you suggested. Version 0.1 is now available on
 HackageDB.

And, of course, natively packaged for Arch,

http://aur.archlinux.org/packages.php?ID=19555

Go, packagers, go! :)

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