[Haskell-cafe] Can we come out of a monad?

2010-07-30 Thread C K Kashyap
Hi,
In the code here -
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=28393#a28393
If I look at the type of modifiedImage, its simply ByteString - but isn't it
actually getting into and back out of the state monad? I am of the
understanding that once you into a monad, you cant get out of it? Is this
breaking the monad scheme?
-- 
Regards,
Kashyap
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Can we come out of a monad?

2010-07-30 Thread Lyndon Maydwell
You cannot break out of a monad if all you have available to use are
the monad typeclass functions, however there is nothing preventing an
instance from being created that allows escape. Many of these escape
methods come in the form of runX functions, but you can use
constructors to break out with pattern matching if they are exposed.

As far as I can tell, IO is more of an outlier in this regard.

(Did I miss something?)

On Fri, Jul 30, 2010 at 2:23 PM, C K Kashyap ckkash...@gmail.com wrote:
 Hi,
 In the code here -
 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=28393#a28393
 If I look at the type of modifiedImage, its simply ByteString - but isn't it
 actually getting into and back out of the state monad? I am of the
 understanding that once you into a monad, you cant get out of it? Is this
 breaking the monad scheme?
 --
 Regards,
 Kashyap

 ___
 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] Can we come out of a monad?

2010-07-30 Thread Jason Dagit
On Thu, Jul 29, 2010 at 11:48 PM, Lyndon Maydwell maydw...@gmail.comwrote:

 You cannot break out of a monad if all you have available to use are
 the monad typeclass functions, however there is nothing preventing an
 instance from being created that allows escape. Many of these escape
 methods come in the form of runX functions, but you can use
 constructors to break out with pattern matching if they are exposed.


There is one case where you can break out of a monad without knowing which
monad it is.  Well, kind of.  It's cheating in a way because it does force
the use of the Identity monad.  Even if it's cheating, it's still very
clever and interesting.
http://okmij.org/ftp/Computation/lem.html

http://okmij.org/ftp/Computation/lem.htmlThe specific function is:

  purify :: (forall m. Monad m = ((a - m b) - m b)) - ((a-b)-b)
  purify f = \k - runIdentity (f (return . k))

We take some arbitrary monad 'm' and escape from it.  Actually, the trick is
that f must work for ALL monads.  So we pick just one that allows escape and
apply f to it.  Here we picked Identity.  You could have picked Maybe,
lists, and any of the others that allow escaping.


 As far as I can tell, IO is more of an outlier in this regard.


Yes I agree there.  And even with IO we have unsafePerformIO that lets you
escape.

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


[Haskell-cafe] Fail to install SDL with Cabal

2010-07-30 Thread Eitan Goldshtrom
I'm trying to install SDL through Cabal -- I don't know another way to 
install it. However, I'm getting this:


setup.exe: The package has a './configure' script. This requires a Unix
compatibility toolchain such as MinGW+MSYS or Cygwin.
cabal: Error: some packages failed to install:
SDL-0.5.10 failed during the configure step. The exception was:
exit: ExitFailure 1

I have MinGW and MSYS, so I don't understand why I'm having this 
problem. Do I need to set something special up so that Cabal can access 
their tools?


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


Re: [Haskell-cafe] Can we come out of a monad?

2010-07-30 Thread Stefan Holdermans
Jason,

 There is one case where you can break out of a monad without knowing which 
 monad it is.  Well, kind of.  It's cheating in a way because it does force 
 the use of the Identity monad.  Even if it's cheating, it's still very clever 
 and interesting.

How is this cheating?  Or better, how is this breaking out of a monad without 
knowing which monad it is?  It isn't. You know exactly which monad you're 
breaking out: it's the identity monad.  That's what happens if you put 
quantifiers in negative positions: here, you are not escaping out of an 
arbitrary monad (which you can't), but escaping out of a very specific monad.

 The specific function is:
   purify :: (forall m. Monad m = ((a - m b) - m b)) - ((a-b)-b)
   purify f = \k - runIdentity (f (return . k))

Cheers,

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


[Haskell-cafe] couchDB

2010-07-30 Thread Andrew U. Frank
a few weeks ago a question was posed on this list for examples how to
use couchDB. i post the 'hello world' for couchDB using the haskell
interface - perhaps it helps other to start! 

a more extensive and complicate example is found at
www.maztravel.com/haskell/mySqlToCouchDB.html

I created with Futon a db names first (i had no luck with names
containing a - or a _ , but have not investigated further). the
runcouchDB' affects the couchDB at localhost.

andrew

ps: if there is a better place to document examples? a wiki on
haskell.org would be nice and should be available for any project in
hackage.
 


{-# LANGUAGE DeriveDataTypeable #-}

module Main ( ) where

import Database.CouchDB
import Data.Data (Typeable)

import Text.JSON


s1 = JSString $ toJSString Peter

m1 = makeObj [(FirstName, s1), (FamilytName, JSString . toJSString
$ Miller)]

mydb1 = db first-- convert db name to checked couchdb
-- problem with - or _ in db names in haskell??

main = do
putStrLn start couchdb tests
(doc, rev) - runCouchDB' $ newDoc mydb1 m1 -- works 

return ()


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


Re: [Haskell-cafe] Can we come out of a monad?

2010-07-30 Thread Anton van Straaten

C K Kashyap wrote:
In the code here - 
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=28393#a28393
If I look at the type of modifiedImage, its simply ByteString - but 
isn't it actually getting into and back out of the state monad? I am of 
the understanding that once you into a monad, you cant get out of it? Is 
this breaking the monad scheme?


modifiedImage uses the execState function, which has the following type:

  execState :: State s a - s - s

In other words, it applies a State monad value to a state, and returns a 
new state.  Its entire purpose is to run the monad and obtain the 
resulting state.


A monadic value of type State s a is a kind of delayed computation 
that doesn't do anything until you apply it to a state, using a function 
like execState or evalState.  Once you do that, the computation runs, 
the monad is evaluated away, and a result is returned.


The issue about not being able to escape that (I think) you're referring 
to applies to the functions within that computation.  A State monad 
computation typically consists of a chain of monadic functions of type 
(a - State s b) composed using bind (=).  A function in that composed 
chain has to return a monadic value, which constrains the ability of 
such a function to escape from the monad.


Within a monadic function, you may deal directly with states and 
non-monadic values, and you may run functions like evalState or 
execState which eliminate monads, but the function still has to return a 
monadic value in the end, e.g. using return to lift an ordinary value 
into the monad.


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


[Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Kevin Jardine
The original poster states that the type of modifiedImage is simply
ByteString but given that it calls execState, is that possible?

Would it not be State ByteString?

Kevin

On Jul 30, 9:49 am, Anton van Straaten an...@appsolutions.com wrote:
 C K Kashyap wrote:
  In the code here -
 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=28393#a28393
  If I look at the type of modifiedImage, its simply ByteString - but
  isn't it actually getting into and back out of the state monad? I am of
  the understanding that once you into a monad, you cant get out of it? Is
  this breaking the monad scheme?

 modifiedImage uses the execState function, which has the following type:

    execState :: State s a - s - s

 In other words, it applies a State monad value to a state, and returns a
 new state.  Its entire purpose is to run the monad and obtain the
 resulting state.

 A monadic value of type State s a is a kind of delayed computation
 that doesn't do anything until you apply it to a state, using a function
 like execState or evalState.  Once you do that, the computation runs,
 the monad is evaluated away, and a result is returned.

 The issue about not being able to escape that (I think) you're referring
 to applies to the functions within that computation.  A State monad
 computation typically consists of a chain of monadic functions of type
 (a - State s b) composed using bind (=).  A function in that composed
 chain has to return a monadic value, which constrains the ability of
 such a function to escape from the monad.

 Within a monadic function, you may deal directly with states and
 non-monadic values, and you may run functions like evalState or
 execState which eliminate monads, but the function still has to return a
 monadic value in the end, e.g. using return to lift an ordinary value
 into the monad.

 Anton
 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://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: Can we come out of a monad?

2010-07-30 Thread Kevin Jardine
Oops, I should have written

IO ByteString

as the State stuff is only *inside* execState.

But a monad none the less?

Kevin

On Jul 30, 9:59 am, Kevin Jardine kevinjard...@gmail.com wrote:
 The original poster states that the type of modifiedImage is simply
 ByteString but given that it calls execState, is that possible?

 Would it not be State ByteString?

 Kevin

 On Jul 30, 9:49 am, Anton van Straaten an...@appsolutions.com wrote:

  C K Kashyap wrote:
   In the code here -
  http://hpaste.org/fastcgi/hpaste.fcgi/view?id=28393#a28393
   If I look at the type of modifiedImage, its simply ByteString - but
   isn't it actually getting into and back out of the state monad? I am of
   the understanding that once you into a monad, you cant get out of it? Is
   this breaking the monad scheme?

  modifiedImage uses the execState function, which has the following type:

     execState :: State s a - s - s

  In other words, it applies a State monad value to a state, and returns a
  new state.  Its entire purpose is to run the monad and obtain the
  resulting state.

  A monadic value of type State s a is a kind of delayed computation
  that doesn't do anything until you apply it to a state, using a function
  like execState or evalState.  Once you do that, the computation runs,
  the monad is evaluated away, and a result is returned.

  The issue about not being able to escape that (I think) you're referring
  to applies to the functions within that computation.  A State monad
  computation typically consists of a chain of monadic functions of type
  (a - State s b) composed using bind (=).  A function in that composed
  chain has to return a monadic value, which constrains the ability of
  such a function to escape from the monad.

  Within a monadic function, you may deal directly with states and
  non-monadic values, and you may run functions like evalState or
  execState which eliminate monads, but the function still has to return a
  monadic value in the end, e.g. using return to lift an ordinary value
  into the monad.

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

 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://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: Can we come out of a monad?

2010-07-30 Thread Kevin Jardine
Or is it possible to call a function in a monad and return a pure
result? I think that is what the original poster was asking?

I know that unsafePerformIO can do this, but I thought that was a bit
of a hack.

I'm still trying to understand how monads interact with types so I am
interested in this as well.

Kevin

On Jul 30, 10:11 am, Kevin Jardine kevinjard...@gmail.com wrote:
 Oops, I should have written

 IO ByteString

 as the State stuff is only *inside* execState.

 But a monad none the less?

 Kevin

 On Jul 30, 9:59 am, Kevin Jardine kevinjard...@gmail.com wrote:

  The original poster states that the type of modifiedImage is simply
  ByteString but given that it calls execState, is that possible?

  Would it not be State ByteString?

  Kevin

  On Jul 30, 9:49 am, Anton van Straaten an...@appsolutions.com wrote:

   C K Kashyap wrote:
In the code here -
   http://hpaste.org/fastcgi/hpaste.fcgi/view?id=28393#a28393
If I look at the type of modifiedImage, its simply ByteString - but
isn't it actually getting into and back out of the state monad? I am of
the understanding that once you into a monad, you cant get out of it? Is
this breaking the monad scheme?

   modifiedImage uses the execState function, which has the following type:

      execState :: State s a - s - s

   In other words, it applies a State monad value to a state, and returns a
   new state.  Its entire purpose is to run the monad and obtain the
   resulting state.

   A monadic value of type State s a is a kind of delayed computation
   that doesn't do anything until you apply it to a state, using a function
   like execState or evalState.  Once you do that, the computation runs,
   the monad is evaluated away, and a result is returned.

   The issue about not being able to escape that (I think) you're referring
   to applies to the functions within that computation.  A State monad
   computation typically consists of a chain of monadic functions of type
   (a - State s b) composed using bind (=).  A function in that composed
   chain has to return a monadic value, which constrains the ability of
   such a function to escape from the monad.

   Within a monadic function, you may deal directly with states and
   non-monadic values, and you may run functions like evalState or
   execState which eliminate monads, but the function still has to return a
   monadic value in the end, e.g. using return to lift an ordinary value
   into the monad.

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

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

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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Anton van Straaten

 On Jul 30, 9:59 am, Kevin Jardine kevinjard...@gmail.com wrote:

 The original poster states that the type of modifiedImage is simply
 ByteString but given that it calls execState, is that possible?
 Would it not be State ByteString?

 Oops, I should have written

 IO ByteString

 as the State stuff is only *inside* execState.

 But a monad none the less?

State is a pure monad that doesn't involve IO.  It works by threading a 
state value through the monadic computation, so old states are discarded 
and new states are passed on, and no actual mutation is involved.  This 
means there's no need to bring IO into it.


If you look at the type signature of execState, you'll see that unless 
the state type 's' involves IO, the return type can't involve IO.


It can help to run little examples of this.  Here's a GHCi transcript:

Prelude :m Control.Monad.State
Prelude Control.Monad.State let addToState :: Int - State Int (); 
addToState x = do s - get; put (s+x)

Prelude Control.Monad.State let mAdd4 = addToState 4
Prelude Control.Monad.State :t mAdd4
m :: State Int ()
Prelude Control.Monad.State let s = execState mAdd4 2
Prelude Control.Monad.State :t s
s :: Int
Prelude Control.Monad.State s
6

In the above, addToState is a monadic function that adds its argument x 
to the current state.  mAdd4 is a monadic value that adds 4 to whatever 
state it's eventually provided with.  When execState provides it with an 
initial state of 2, the monadic computation is run, and the returned 
result is 6, which is an Int, not a monadic type.



Or is it possible to call a function in a monad and return a pure
result? I think that is what the original poster was asking?


If you use a function like execState (depending on the monad), you can 
typically run a monadic computation and get a non-monadic result. 
However, if you're doing that inside a monadic function, you still have 
to return a value of monadic type - so typically, you use 'return', 
which lifts a value into the monad.



I know that unsafePerformIO can do this, but I thought that was a bit
of a hack.


IO is a special monad which has side effects.  unsafePerformIO is just 
one of the functions that can run IO actions, but because the monad has 
side effects, this is unsafe in general.  With a pure monad like State, 
there's no such issue.


Anton

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


[Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Kevin Jardine
I think that these are therefore the responses to the original
questions:

 I am of the understanding that once you into a monad, you cant get out of it?

You can run monadic functions and get pure results. So it looks like
in that sense you can get out of it.

  Is this breaking the monad scheme?

Apparently not. Although functions that do this for monads that have
side effects are unsafe, so use them carefully.

Cheers,
Kevin

On Jul 30, 11:17 am, Anton van Straaten an...@appsolutions.com
wrote:
   On Jul 30, 9:59 am, Kevin Jardine kevinjard...@gmail.com wrote:
  
   The original poster states that the type of modifiedImage is simply
   ByteString but given that it calls execState, is that possible?
   Would it not be State ByteString?

   Oops, I should have written
  
   IO ByteString
  
   as the State stuff is only *inside* execState.
  
   But a monad none the less?

 State is a pure monad that doesn't involve IO.  It works by threading a
 state value through the monadic computation, so old states are discarded
 and new states are passed on, and no actual mutation is involved.  This
 means there's no need to bring IO into it.

 If you look at the type signature of execState, you'll see that unless
 the state type 's' involves IO, the return type can't involve IO.

 It can help to run little examples of this.  Here's a GHCi transcript:

 Prelude :m Control.Monad.State
 Prelude Control.Monad.State let addToState :: Int - State Int ();
 addToState x = do s - get; put (s+x)
 Prelude Control.Monad.State let mAdd4 = addToState 4
 Prelude Control.Monad.State :t mAdd4
 m :: State Int ()
 Prelude Control.Monad.State let s = execState mAdd4 2
 Prelude Control.Monad.State :t s
 s :: Int
 Prelude Control.Monad.State s
 6

 In the above, addToState is a monadic function that adds its argument x
 to the current state.  mAdd4 is a monadic value that adds 4 to whatever
 state it's eventually provided with.  When execState provides it with an
 initial state of 2, the monadic computation is run, and the returned
 result is 6, which is an Int, not a monadic type.

  Or is it possible to call a function in a monad and return a pure
  result? I think that is what the original poster was asking?

 If you use a function like execState (depending on the monad), you can
 typically run a monadic computation and get a non-monadic result.
 However, if you're doing that inside a monadic function, you still have
 to return a value of monadic type - so typically, you use 'return',
 which lifts a value into the monad.

  I know that unsafePerformIO can do this, but I thought that was a bit
  of a hack.

 IO is a special monad which has side effects.  unsafePerformIO is just
 one of the functions that can run IO actions, but because the monad has
 side effects, this is unsafe in general.  With a pure monad like State,
 there's no such issue.

 Anton

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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Anton van Straaten

Kevin Jardine wrote:

I think that these are therefore the responses to the original
questions:


I am of the understanding that once you into a monad, you cant get out of it?


You can run monadic functions and get pure results. 


Some clarifications:

First, many monads (including State) are completely pure in a 
referential transparency sense, so the issue we're discussing is not a 
question of whether results are pure (in general) but rather whether 
they're monadic or not, i.e. whether the type of a result is something 
like Monad m = m a, or just a.


Second, what I was calling a monadic function is a function of type:

  Monad m = a - m b

These are the functions that bind (=) composes.  When you apply these 
functions to a value of type a, you always get a monadic value back of 
type m b, because the type says so.


These functions therefore *cannot* do anything to escape the monad, 
and by the same token, a chain of functions composed with bind, or the 
equivalent sequence of statements in a 'do' expression, cannot escape 
the monad.


It is only the monadic values (a.k.a. actions) of type m b that you 
can usually run using a runner function specific to the monad in 
question, such as execState (or unsafePerformIO).


(Note that as Lyndon Maydwell pointed out, you cannot escape a monad 
using only Monad type class functions.)



So it looks like in that sense you can get out of it.


At this level, you can think of a monad like a function (which it often 
is, in fact).  After you've applied a function to a value and got the 
result, you don't need the function any more.  Ditto for a monad, except 
that for monads, the applying is usually done by a monad-specific runner 
function.


Anton

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


[Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Kevin Jardine
I think that we are having a terminology confusion here. For me, a
pure function is one that does not operate inside a monad. Eg. ++,
map, etc.

It was at one point my belief that although code in monads could call
pure functions, code in pure functions could not call functions that
operated inside a monad.

I was then introduced to functions such as execState and
unsafePerformIO which appear to prove that my original belief was
false.

Currently I am in a state of deep confusion, but that is OK, because
it means that I am learning something new!

Kevin

On Jul 30, 11:55 am, Anton van Straaten an...@appsolutions.com
wrote:
 Kevin Jardine wrote:
  I think that these are therefore the responses to the original
  questions:

  I am of the understanding that once you into a monad, you cant get out of 
  it?

  You can run monadic functions and get pure results.

 Some clarifications:

 First, many monads (including State) are completely pure in a
 referential transparency sense, so the issue we're discussing is not a
 question of whether results are pure (in general) but rather whether
 they're monadic or not, i.e. whether the type of a result is something
 like Monad m = m a, or just a.

 Second, what I was calling a monadic function is a function of type:

    Monad m = a - m b

 These are the functions that bind (=) composes.  When you apply these
 functions to a value of type a, you always get a monadic value back of
 type m b, because the type says so.

 These functions therefore *cannot* do anything to escape the monad,
 and by the same token, a chain of functions composed with bind, or the
 equivalent sequence of statements in a 'do' expression, cannot escape
 the monad.

 It is only the monadic values (a.k.a. actions) of type m b that you
 can usually run using a runner function specific to the monad in
 question, such as execState (or unsafePerformIO).

 (Note that as Lyndon Maydwell pointed out, you cannot escape a monad
 using only Monad type class functions.)

  So it looks like in that sense you can get out of it.

 At this level, you can think of a monad like a function (which it often
 is, in fact).  After you've applied a function to a value and got the
 result, you don't need the function any more.  Ditto for a monad, except
 that for monads, the applying is usually done by a monad-specific runner
 function.

 Anton

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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Daniel Díaz
I don't understand why to call impure to the types instances of a class.
Monad is simply a class with their methods. Even the pure list is a monad.
The only difference between Monad and other classes is do notation, and only
affects notation.

The impure side is a type, not a class: IO.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Ivan Lazar Miljenovic
Kevin Jardine kevinjard...@gmail.com writes:

 I think that we are having a terminology confusion here. For me, a
 pure function is one that does not operate inside a monad. Eg. ++,
 map, etc.

No, a pure function is one without any side effects.

 It was at one point my belief that although code in monads could call
 pure functions, code in pure functions could not call functions that
 operated inside a monad.

Not at all.  I can do something like map (liftM succ) [Just 2,
Nothing], where liftM is a monadic function.  The thing is that I'm
applying it to a pure monad (i.e. the Maybe monad doesn't have side
effects).

 I was then introduced to functions such as execState and
 unsafePerformIO which appear to prove that my original belief was
 false.

unsafePerformIO is the wild-card here; it's whole purpose is to be able
to say that this IO action (usually linking to a C library or some
such) is pure, promise!!!.

 Currently I am in a state of deep confusion, but that is OK, because
 it means that I am learning something new!

The big point here that you seem to be tied up in is that Monad /=
impure.

I see three broad classifications of Monads:

1) Data structures that can be used as monads, such as [a] and Maybe a.

2) Special monadic wrappers/transformers such as State, Reader,
   etc. which allow you to act as if something is being done
   sequentially (which is the whole point of =) but is actually a pure
   function.  The ST monad also appears to be able to be used like this
   if you use runST.

3) Side-effect monads: IO, STM, ST (used with stToIO), etc.  The
   classical monads, so to speak which you seem to be thinking about.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Can we come out of a monad?

2010-07-30 Thread Tillmann Rendel

C K Kashyap wrote:

I am of the
understanding that once you into a monad, you cant get out of it? 


That's not correct.

There are many monads, including Maybe, [], IO, ... All of these monads 
provide operations (=), return and fail, and do notation implemented 
in terms of these functions, as a common interface. Using just this 
common interface, you cannot get out of the monad.


But most if not all monads also provide additional operations, specific 
to the monad in question. Often, these operations can be used to get 
out of that monad. For example, with Maybe, you can use pattern matching:


  case do x - return 5
  fail some message
  return (x + 3) of
Just a   -  a
Nothing  -  0

So we can get out of many monads, but we need to know which one it is to 
use the appropriate operation.


Kevin Jardine wrote:

I'm still trying to understand how monads interact with types so I am
interested in this as well.


From my point of view, the most important fact about monads is:

  There is nothing special about monads!

The type class Monad behaves like very other type class. A monadic type 
constructor behaves like every other type constructor. The type class 
methods (=), return and fail behave like every other type class 
method. There is nothing special about monads.


The only speciality of monads is do notation, but do notation is only a 
syntactic convenience, and can be translated into calls of (=), return 
and fail, which, as noted above, are not special in any way.


So, back to your question, since there is nothing special about monads, 
monads do not interact with types in any special way.


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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Anton van Straaten

Kevin Jardine wrote:

I think that we are having a terminology confusion here. For me, a
pure function is one that does not operate inside a monad. Eg. ++,
map, etc.


Ivan Miljenovic has already given a good response, to which I'll only 
add this:


I suspect that your idea of the meaning of purity came from 
over-generalization from the IO monad.  IO actions may be impure, but 
that's not true of all other monad types.  (Most are actually pure.)


Really, the IO monad is a horrible exception to normal monadic behavior, 
and in an ideal world it should only be introduced as a special case 
after gaining a good understanding of monads in general.


Of course in practice, people like their programs to be able to do I/O, 
so the IO monad ends up being one of the first things learned.


It's a bit like teaching a new carpenter about the concept of tools, 
and then starting them out with a chainsaw, leading to the natural 
conclusion that tools are loud, insanely dangerous things.


Anton

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


[Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Kevin Jardine
So far the comments here only increase my confusion (which as I say,
is not bad because it means that I am learning something!).

As a Haskell newbie, the first thing I learned about monads is that
they have a type signature that creates a kind of mud you can't wash
off.

eg.

f :: String - MyMonad String

By mentioning the monad, you get to use its special functions but as a
hard price, you must return a value with a type signature that locks
it within the monad (although you can remove the signature within
other monads using -).

As some people have hinted, perhaps the problem is that most Haskell
newbies are introduced to monads through the IO monad and other monads
are different.

When I plunged into Haskell earlier this year, I had no problem with
understanding static typing, higher level functions and even
separating pure functions from IO functions.

The more I learn about monads, however, the less I understand them.
I've seen plenty of comments suggesting that monads are easy to
understand, but for me they are not.

Cheers,
Kevin

On Jul 30, 12:29 pm, Tillmann Rendel ren...@informatik.uni-
marburg.de wrote:
 C K Kashyap wrote:
  I am of the
  understanding that once you into a monad, you cant get out of it?

 That's not correct.

 There are many monads, including Maybe, [], IO, ... All of these monads
 provide operations (=), return and fail, and do notation implemented
 in terms of these functions, as a common interface. Using just this
 common interface, you cannot get out of the monad.

 But most if not all monads also provide additional operations, specific
 to the monad in question. Often, these operations can be used to get
 out of that monad. For example, with Maybe, you can use pattern matching:

    case do x - return 5
            fail some message
            return (x + 3) of
      Just a   -  a
      Nothing  -  0

 So we can get out of many monads, but we need to know which one it is to
 use the appropriate operation.

 Kevin Jardine wrote:
  I'm still trying to understand how monads interact with types so I am
  interested in this as well.

  From my point of view, the most important fact about monads is:

    There is nothing special about monads!

 The type class Monad behaves like very other type class. A monadic type
 constructor behaves like every other type constructor. The type class
 methods (=), return and fail behave like every other type class
 method. There is nothing special about monads.

 The only speciality of monads is do notation, but do notation is only a
 syntactic convenience, and can be translated into calls of (=), return
 and fail, which, as noted above, are not special in any way.

 So, back to your question, since there is nothing special about monads,
 monads do not interact with types in any special way.

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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Colin Paul Adams
 Kevin == Kevin Jardine kevinjard...@gmail.com writes:

Kevin The more I learn about monads, however, the less I understand
Kevin them.  I've seen plenty of comments suggesting that monads
Kevin are easy to understand, but for me they are not.

I used to have the same problem.

Then I read:

http://ertes.de/articles/monads.html

and after that it was very clear.
-- 
Colin Adams
Preston Lancashire
()  ascii ribbon campaign - against html e-mail
/\  www.asciiribbon.org   - against proprietary attachments
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Ivan Lazar Miljenovic
Anton van Straaten an...@appsolutions.com writes:

 Ivan Miljenovic has already given a good response

Why thank you, kind sir!

/me bows

 I suspect that your idea of the meaning of purity came from
 over-generalization from the IO monad.  IO actions may be impure, but
 that's not true of all other monad types.  (Most are actually pure.)

 Really, the IO monad is a horrible exception to normal monadic
 behavior, and in an ideal world it should only be introduced as a
 special case after gaining a good understanding of monads in general.

Actually, the general consensus seems to be nowadays that people should
be taught IO without any mentions to monads at all (there are various
tutorials around, and if memory serves RWH does this as well), then
introduce the concept of monads and then say oh, btw, that IO thing
we've been using all this time?  It's also one of these weird monad
things.

 It's a bit like teaching a new carpenter about the concept of tools,
 and then starting them out with a chainsaw, leading to the natural
 conclusion that tools are loud, insanely dangerous things.

Heh, I like this analogy.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Ivan Lazar Miljenovic
Kevin Jardine kevinjard...@gmail.com writes:

 The more I learn about monads, however, the less I understand them.
 I've seen plenty of comments suggesting that monads are easy to
 understand, but for me they are not.

How did you learn monads?

More and more people seem to be getting away from trying to say that
monads are containers/burritos/etc. and just teaching them by way of the
definition, either = and return or just join (ignoring that wart known
as fail); Tillman alluded to this approach earlier.

One way of doing so (e.g. by RWH) is to use these definitions in a
specific (non-IO) monad (usually a parser) and then generalise them.  If
you want an alternative to RWH that takes this approach, I've found Tony
Morris' take on this to be reasonable:

Slides (currently seem to be down):
http://projects.tmorris.net/public/what-does-monad-mean/artifacts/1.0/chunk-html/index.html
 

Video: http://vimeo.com/8729673

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fail to install SDL with Cabal

2010-07-30 Thread Stephen Tetley
Hi Eitan

You will probably need to do a manual install.

If you download and extract the SDL binding there is a file - WIN32 -
in the top level directory describing how to install on Windows.
Unfortunately this file might now be out-of-date. I haven't used the
Haskell SDL binding myself since version 0.5.3 which was quite a while
ago, and then the WIN32 file was a message describing Bit Connor's
successful install - it might still be the same file.

As the SDL developers distribute a DLL of the C library, you can build
the binding with either Cygwin or MinGW. MinGW is probably the better
choice these days though. Again, unfortunately I don't have experience
of building it with MinGW to share, you might have to do some
improvisation to get it to work.


Best wishes

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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Brent Yorgey
On Fri, Jul 30, 2010 at 03:46:09AM -0700, Kevin Jardine wrote:
 
 When I plunged into Haskell earlier this year, I had no problem with
 understanding static typing, higher level functions and even
 separating pure functions from IO functions.
 
 The more I learn about monads, however, the less I understand them.
 I've seen plenty of comments suggesting that monads are easy to
 understand, but for me they are not.

Lies.  Monads are not easy to understand.  Anyone who says otherwise
is selling something (likely a monad tutorial that they wrote).  Or
else they are saying it out of a well-meaning but misguided idea that
telling people that monads are easy will make it so, because the real
problem with monads is only that people THINK they are hard.  So if
only everyone stopped freaking out and realized that learning about
monads is actually easy, perhaps helped by a playing a recorded voice
at night crooning to you in soothing tones that you can achieve
anything you like by just visualizing your success and realizing that
you have already had the power within you all along, then learning
monads will be a snap!

Lies.  

Even worse, this misguided but common insistence that monads are easy
to understand inevitably makes people feel stupid when they discover
that they aren't.

Monads are hard to understand.  But they are *worth understanding*.

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


[Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Kevin Jardine
On Jul 30, 1:11 pm, Brent Yorgey byor...@seas.upenn.edu wrote:

 Monads are hard to understand.  But they are *worth understanding*.

That's the most inspiring and encouraging statement I've seen all
week.

Thanks!

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


Re: [Haskell-cafe] Can we come out of a monad?

2010-07-30 Thread Martijn van Steenbergen

On 7/30/10 9:29, Stefan Holdermans wrote:

Jason,


There is one case where you can break out of a monad without knowing which 
monad it is.  Well, kind of.  It's cheating in a way because it does force the 
use of the Identity monad.  Even if it's cheating, it's still very clever and 
interesting.


How is this cheating?  Or better, how is this breaking out of a monad without 
knowing which monad it is?  It isn't. You know exactly which monad you're breaking 
out: it's the identity monad.  That's what happens if you put quantifiers in negative 
positions: here, you are not escaping out of an arbitrary monad (which you can't), but 
escaping out of a very specific monad.


Also, the only monadic functions the argument may use are return, bind 
and fail. It's hard to do something useful with only those functions.



The specific function is:
purify :: (forall m. Monad m =  ((a -  m b) -  m b)) -  ((a-b)-b)
purify f = \k -  runIdentity (f (return . k))


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


Re: [Haskell-cafe] Can we come out of a monad?

2010-07-30 Thread Martijn van Steenbergen

On 7/30/10 12:29, Tillmann Rendel wrote:

C K Kashyap wrote:

I am of the
understanding that once you into a monad, you cant get out of it?


That's not correct.

There are many monads, including Maybe, [], IO, ... All of these monads
provide operations (=), return and fail, and do notation implemented
in terms of these functions, as a common interface. Using just this
common interface, you cannot get out of the monad.

But most if not all monads also provide additional operations, specific
to the monad in question. Often, these operations can be used to get
out of that monad. For example, with Maybe, you can use pattern matching:


In fact, I would argue that a monad which you cannot escape from is not 
very useful at all. IO is the only exception I know of.


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


Re: [Haskell-cafe] Can we come out of a monad?

2010-07-30 Thread Ivan Lazar Miljenovic
Martijn van Steenbergen mart...@van.steenbergen.nl writes:

 On 7/30/10 12:29, Tillmann Rendel wrote:
 C K Kashyap wrote:
 I am of the
 understanding that once you into a monad, you cant get out of it?

 That's not correct.

 There are many monads, including Maybe, [], IO, ... All of these monads
 provide operations (=), return and fail, and do notation implemented
 in terms of these functions, as a common interface. Using just this
 common interface, you cannot get out of the monad.

 But most if not all monads also provide additional operations, specific
 to the monad in question. Often, these operations can be used to get
 out of that monad. For example, with Maybe, you can use pattern matching:

 In fact, I would argue that a monad which you cannot escape from is
 not very useful at all. IO is the only exception I know of.

True; all other monads allow you to at least get into IO (STM, etc.).

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Tillmann Rendel

Hi,

I wrote:

There is nothing special about monads!


Kevin Jardine wrote:

I've seen plenty of comments suggesting that monads are easy to
understand, but for me they are not.


My point was that monads are not a language feature whith special 
treatment of the compiler, but more like a design pattern or a standard 
interface, a way of using the language. There is no compiler magic about 
monads. Therefore, they can, in principle, be understand by reading 
their definition in Haskell.


Nevertheless, I agree that it is hard to understand monads, because they 
are a clever way of using Haskell and use several of Haskell's more 
advanced features.


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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Anton van Straaten

Kevin Jardine wrote:

As a Haskell newbie, the first thing I learned about monads is that
they have a type signature that creates a kind of mud you can't wash
off.


There are places where you can't wash it off, and places where you can.


eg.

f :: String - MyMonad String

By mentioning the monad, you get to use its special functions but as a
hard price, you must return a value with a type signature that locks
it within the monad


That's perfectly correct: you must return a value with a type signature 
that locks it within the monad.  That's because you're referring here 
to returning a value from a monadic function with a return type of 
MyMonad String.  But that's just one part of the picture.


Consider a caller of that function: after applying f to some string, it 
ends up with a value of type MyMonad String.  One of the things you can 
typically do with such values is wash off the mud using a runner 
function, specific to the monad.


They're called runners (informally) because what they do is run the 
delayed computation represented by the monad.  In the case of the State 
monad, the runner takes an initial state and supplies it to the monad in 
order to start the computation.  If these runners didn't exist, the 
monad would be rather useless, because it would never actually execute. 
 The result of running that computation typically eliminates the monad 
type - the mud is washed off.


You can even do this inside a monadic function, e.g.:

g m = do s - get
 let x = evalState m s   -- wash the mud off m !
 ...

But the value of x above will be locked inside the function - you can't 
return such values to the caller without using e.g. return x, to 
return a monadic value.


So you may be able to wash the mud off a monadic value, but if you want 
to pass that value outside a monadic function you have to put the mud 
back on first.


However, if you have a monadic value *outside* a monadic function, no 
such rule applies.



The more I learn about monads, however, the less I understand them.
I've seen plenty of comments suggesting that monads are easy to
understand, but for me they are not.


Monads are very general, which means they're not easily learned by the 
common style of extrapolating from examples.  They're easy to understand 
in hindsight though!  :-}


Anton

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


Re: [Haskell-cafe] Can we come out of a monad?

2010-07-30 Thread Stefan Holdermans
Martijn,

 In fact, I would argue that a monad which you cannot escape from is not very 
 useful at all. IO is the only exception I know of.

And that's only because, at least the runtime system allows for execution of a 
computation inside the IO monad at top-level.

Cheers,

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


Re: [Haskell-cafe] Fail to install SDL with Cabal

2010-07-30 Thread Job Vranish
You might try emailing the maintainer directly. The package appears to be
actively maintained.

- Job

On Fri, Jul 30, 2010 at 3:17 AM, Eitan Goldshtrom thesource...@gmail.comwrote:

  I'm trying to install SDL through Cabal -- I don't know another way to
 install it. However, I'm getting this:

 setup.exe: The package has a './configure' script. This requires a Unix
 compatibility toolchain such as MinGW+MSYS or Cygwin.
 cabal: Error: some packages failed to install:
 SDL-0.5.10 failed during the configure step. The exception was:
 exit: ExitFailure 1

 I have MinGW and MSYS, so I don't understand why I'm having this problem.
 Do I need to set something special up so that Cabal can access their tools?

 -Eitan

 ___
 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] [Yi Editor]Cabal Problem

2010-07-30 Thread Job Vranish
I think you can just install the windows gtk dev libraries from here:
http://www.gtk.org/download.html

- Job

On Thu, Jul 29, 2010 at 5:20 PM, Alessandro Stamatto astama...@gmail.comwrote:

 Installing Yi Editor i get the following error:
 --
 ---
 Missing dependencies on foreign libraries:
 * Missing C libraries: gobject-2.0, glib-2.0, intl, iconv

 -

 Im on windows, using Cabal in Cygwin.

 How should i install those missing libs?

 ___
 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] couchDB

2010-07-30 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 7/30/10 03:31 , Andrew U. Frank wrote:
 ps: if there is a better place to document examples? a wiki on
 haskell.org would be nice and should be available for any project in
 hackage.

haskell.org has (more precisely, *is*) a wiki; request an account
(http://haskell.org/haskellwiki/?title=Special:Userloginreturnto=Haskell)
and go nuts.

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkxS3ooACgkQIn7hlCsL25XYngCeLUJze41lkwlxXW0hsBTLhWBo
d3cAn2FNQYNUn8kTczX6kFdbB5aKxGyp
=hhDi
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Ertugrul Soeylemez
Hello,

it's a bit hidden in Haskell, but a monad instance consists of three
functions:

  fmap   :: (a - b) - (m a - m b)
  return :: a - m a
  join   :: m (m a) - m a

Nothing more is needed to define a monad.  In Haskell, a monad is
expressed by 'return' and (=) instead, but this is equivalent.

The types of these functions tell you what you can do with the monad.
You can put values into it and you can turn a doubly wrapped monadic
value into a singly wrapped monadic value (usually by dropping
information).

Unless there is a function, which has deeper comprehension of a monadic
value than these two functions, like 'runState' or 'head', you can never
get values out of it.  For the IO monad no such function can exist.
This is intentional.


Greets,
Ertugrul


C K Kashyap ckkash...@gmail.com wrote:

 Hi,
 In the code here -
 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=28393#a28393
 If I look at the type of modifiedImage, its simply ByteString - but isn't it
 actually getting into and back out of the state monad? I am of the
 understanding that once you into a monad, you cant get out of it? Is this
 breaking the monad scheme?



-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/


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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Ivan Lazar Miljenovic
Ertugrul Soeylemez e...@ertes.de writes:

 Hello,

 it's a bit hidden in Haskell, but a monad instance consists of three
 functions:

   fmap   :: (a - b) - (m a - m b)

You don't even need fmap defined for it to be a monad, since fmap f m =
liftM f m = m = (return . f)

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 7/30/10 06:06 , Kevin Jardine wrote:
 I think that we are having a terminology confusion here. For me, a
 pure function is one that does not operate inside a monad. Eg. ++,
 map, etc.
 
 It was at one point my belief that although code in monads could call
 pure functions, code in pure functions could not call functions that
 operated inside a monad.
 
 I was then introduced to functions such as execState and
 unsafePerformIO which appear to prove that my original belief was
 false.
 
 Currently I am in a state of deep confusion, but that is OK, because
 it means that I am learning something new!

A monad is just a wrapper that lets you take an action of some kind whenever
the wrapped value is operated on.

Pure means referentially transparent; that is, it should always be
possible to substitute an expression for its expansion without changing its
meaning.

Now, certain specific monads (IO, ST, STM) are used specifically for
operations that are *not* referentially transparent.  Those operations are
therefore confined to occurring only within the monad wrapper; ST allows you
to extract a referentially transparent value (although it's up to the
programmer to enforce that, and the only consequences for violation are
potential odd program behaviors), the others do not without doing evil things.

*** Eye-bleedy ahead; skip the next paragraph if you are in over your head. ***

In the case of ST and STM, it is possible to pull values back out; in the
case of ST, this means that non-referentially-transparent operations can
take place behind the curtain as long as what emerges from the curtain is
the same as would happen with a referentially transparent version (this is
used when it's more efficient to alter values in place than to produce new
values), while STM operations can only be extracted to IO (STM is in some
sense an extension of IO) and IO operations can only be extracted by running
the program or using unsafePerformIO (or its cousins unsafeInterleaveIO and
unsafeIOtoST/unsafeSTtoIO), which are labeled unsafe specifically because
they're exposing non-referentially-transparent operations which are
therefore capable of causing indeterminate program behavior.

*** resuming the flow ***

The majority of monads (State, Writer, Reader, etc.) are entirely
referentially transparent in their workings; in these cases, the wrapper is
used simply to add a hook that is itself referentially transparent.  The
three mentioned above are all quite similar, in that the hook just carries
a second value along and the monad definition includes functions that can
operate on that value (get, gets, put, modify; tell; ask, asks, local).
Other referentially transparent monads are used to provide controllable
modification of control flow:  Maybe and (Either a) let you short-circuit
evaluation based on a notion of failure; list aka [] lets you operate on
values in parallel, with backtracking when a branch fails.  Cont is the
ultimate expression of this, in effect allowing the hook to be evaluated
at any time by the wrapped operation; as such, it's worth studying, but it
will probably warp your brain a bit.  (It's possible to derive any of the
referentially transparent monads from Cont.)

The distinction between these two classes, btw, lies in whether the hook
allows things to escape.  In the case of ST, IO, and STM, the hook carries
around an existentially qualified type, which by definition cannot be given
a type outside of the wrapper.  (Think of it this way:  it's existentially
qualified because its existence is qualified to only apply within the wrapper.)

*** more eye-bleedy ahead ***

In many IO implementations, IO is just ST with a magic value that can
neither be created nor modified nor destroyed, simply passed around.  The
value is meaningless (and, in ghc, at least, nonexistent!); only its type is
significant, because the type prevents anything using it from escaping.  The
other half of this trick is that operations in IO quietly use (by
reference) this value, so that they are actually partially applied
functions; this is why we refer to IO actions.  An action in this case
is simply a partially applied function which is waiting for the magic
(non-)value to be injected into it before it can produce a value.  In
effect, it's a baton passed between actions to insure that they take place
in sequence.  And this is why the unsafe functions are unsafe; they allow
violation of the sequence enforced by the baton.  unsafePerformIO goes
behind the runtime's back to pull a copy of the baton out of the guts of the
runtime and feeds it to an I/O action; unsafeInterleaveIO clones the
baton(!); unsafeIOtoST doesn't actually do anything other than hide the
baton, but the only thing you can do with it then is pass it to unsafeSTtoIO
- --- which is really unsafePerformIO under the covers.  (The purpose of those
two functions is that ST's mutable arrays are identical to IO's mutable
arrays, and 

Re: [Haskell-cafe] Can we come out of a monad?

2010-07-30 Thread Alex Rozenshteyn
Here is my understanding with respect to the question.

In the general case, you cannot come out of a monad, because the monad
typeclass does not include any functions without of the form (m a - a).

Also, as a category theoretic construct, a monad does not have to have an
exit function. (caveat: I have a very limited grasp of what that means).

I also found myself thinking about list as a monad in terms of this
discussion.  I think it's an interesting case:  it's pure, but it doesn't
really make sense to come out of it.  Head, indexing, and last all break
out of it, but none of them can be the default, and all of them require you
to consider it as something more than its monad-ness.

On Fri, Jul 30, 2010 at 3:11 PM, Stefan Holdermans ste...@vectorfabrics.com
 wrote:

 Martijn,

  In fact, I would argue that a monad which you cannot escape from is not
 very useful at all. IO is the only exception I know of.

 And that's only because, at least the runtime system allows for execution
 of a computation inside the IO monad at top-level.

 Cheers,

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




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


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 7/30/10 11:48 , Ivan Lazar Miljenovic wrote:
 Ertugrul Soeylemez e...@ertes.de writes:
 it's a bit hidden in Haskell, but a monad instance consists of three
 functions:

   fmap   :: (a - b) - (m a - m b)
 
 You don't even need fmap defined for it to be a monad, since fmap f m =
 liftM f m = m = (return . f)

fmap/join and return/bind are isomorphic; given either set, you can produce
the other.  The usual category-theory definition of monads uses the former;
Haskell uses the latter, because it allows operations to easily be chained
together.

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkxS9foACgkQIn7hlCsL25Uc2ACgoLG8uti3d0oWrv1H56fRJ3W4
xZIAn1KotatZklktHpKEwdib6AKXrNOr
=Io9w
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] OpenGL Speed!

2010-07-30 Thread Henning Thielemann
Vo Minh Thu schrieb:

 There other possibilities to deal with raster graphics:
 - Use gtk; i.e. something like
 http://hackage.haskell.org/package/AC-EasyRaster-GTK
 - Output the data in some image format (if you want to do it yourself,
 the most simple is PPM)
 - Use X11 directly (if you're on unix)
 - ...

or good old HGL:
http://hackage.haskell.org/package/HGL
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Re: Can we come out of a monad?

2010-07-30 Thread Jason Catena
On Jul 30, 11:17 am, Anton van Straaten wrote:
 Prelude :m Control.Monad.State
 Prelude Control.Monad.State let addToState :: Int - State Int ();
 addToState x = do s - get; put (s+x)
 Prelude Control.Monad.State let mAdd4 = addToState 4
 Prelude Control.Monad.State :t mAdd4
 m :: State Int ()
 Prelude Control.Monad.State let s = execState mAdd4 2
 Prelude Control.Monad.State :t s
 s :: Int
 Prelude Control.Monad.State s
 6

By this example State doesn't seem to give you anything more than a
closure would, since it doesn't act like much of an accumulator (by,
for example, storing 6 as its new internal value).

Could you use State for something like storing the latest two values
of a Fibonacci series?  For example, each time you call it, it
generates the next term, discards the oldest term, and stores the
newly-generated term?

And could you then use this Fibonacci State monad in a lazy
computation, to grab for example the first twenty even Fibonacci
numbers, without computing and storing the series beyond what the
filter asks for?

We can generate Fibonacci series double-recursively in a lazy
computation.  Would it be more or less efficient to use a Fibonacci
State monad instead?  Would the State implementation provide a larger
range before it blew the stack (which tail-recursion should prevent),
or became too slow for impatient people?

Would Haskell memoize already-generated values in either case?  Could
we write a general memoizer across both the recursive and State
implementations, or must we write a specific one to each case?

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


Re: [Haskell-cafe] Can we come out of a monad?

2010-07-30 Thread Jason Dagit
On Fri, Jul 30, 2010 at 12:29 AM, Stefan Holdermans 
ste...@vectorfabrics.com wrote:

 Jason,

  There is one case where you can break out of a monad without knowing
 which monad it is.  Well, kind of.  It's cheating in a way because it does
 force the use of the Identity monad.  Even if it's cheating, it's still very
 clever and interesting.

 How is this cheating?  Or better, how is this breaking out of a monad
 without knowing which monad it is?  It isn't. You know exactly which monad
 you're breaking out: it's the identity monad.  That's what happens if you
 put quantifiers in negative positions: here, you are not escaping out of an
 arbitrary monad (which you can't), but escaping out of a very specific
 monad.

  The specific function is:
purify :: (forall m. Monad m = ((a - m b) - m b)) -
 ((a-b)-b)
purify f = \k - runIdentity (f (return . k))


I guess I refer to it as cheating because the type signature of purify is
surprising the first time you see it, even if perfectly logical.

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


Re: [Haskell-cafe] OpenGL Speed!

2010-07-30 Thread Henning Thielemann


On Fri, 30 Jul 2010, Eitan Goldshtrom wrote:


HGL actually looks like EXACTLY what I need. I only need to set pixels, which 
looks like
just what HGL would be good at. Only problem is that I can't find a single 
tutorial for
HGL. Does anyone know or any, or where I could find one?


I found the Haddock documentation enough for what I tried. Maybe my 
example can help you:

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


Re: [Haskell-cafe] OpenGL Speed!

2010-07-30 Thread Eitan Goldshtrom
HGL actually looks like EXACTLY what I need. I only need to set pixels, 
which looks like just what HGL would be good at. Only problem is that I 
can't find a single tutorial for HGL. Does anyone know or any, or where 
I could find one?


-Eitan

On 7/30/2010 12:22 PM, Henning Thielemann wrote:

Vo Minh Thu schrieb:

   

There other possibilities to deal with raster graphics:
- Use gtk; i.e. something like
http://hackage.haskell.org/package/AC-EasyRaster-GTK
- Output the data in some image format (if you want to do it yourself,
the most simple is PPM)
- Use X11 directly (if you're on unix)
- ...
 

or good old HGL:
http://hackage.haskell.org/package/HGL
   
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Definition of List type?

2010-07-30 Thread michael rice
From: Data.Maybe

Description
The Maybe type, and associated operations.


From: Data.List

Description
Operations on lists.


One description has the type and associated operations, the other only has the 
operations.

Where can I find the type definition for List, and why isn't it in Data.List? 

Michael




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


Re: [Haskell-cafe] Definition of List type?

2010-07-30 Thread Edward Z. Yang
Excerpts from michael rice's message of Fri Jul 30 14:41:44 -0400 2010:
 One description has the type and associated operations, the other only has 
 the operations.
 
 Where can I find the type definition for List, and why isn't it in Data.List? 

Hello Michael,

This is because the List datatype is built into Haskell.  A close approximation
to it would be:

data List a = Nil | Cons a (List a)

where

List a  is [a] (type)
Nil is [] (constructor)
Const x xs  is x:xs (constructor)

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


Re: [Haskell-cafe] Definition of List type?

2010-07-30 Thread Gregory Crosswhite
 List are actually built in to the language, but they are roughly
equivalent to the following definition:

data List a =
[]
 |  a:List a

The reason why this definition never actually appears is because it
defines the constructors using operators rather than names, which is not
allowed in vanilla Haskell.  (There is an extension, TypeOperators,
however, that does allow this.)

Cheers,
Greg

On 07/30/10 11:41, michael rice wrote:
 From: Data.Maybe

 Description
 The Maybe type, and associated operations.


 From: Data.List

 Description
 Operations on lists.


 One description has the type and associated operations, the other only
 has the operations.

 Where can I find the type definition for List, and why isn't it in
 Data.List?

 Michael



 ___
 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] Definition of List type?

2010-07-30 Thread Edward Z. Yang
Excerpts from Edward Z. Yang's message of Fri Jul 30 14:48:34 -0400 2010:
 Const x xs  is x:xs (constructor)

That should be a Cons, not Const. :o)

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


Re: [Haskell-cafe] Definition of List type?

2010-07-30 Thread Ben Millwood
On Fri, Jul 30, 2010 at 7:50 PM, Gregory Crosswhite
gcr...@phys.washington.edu wrote:

 The reason why this definition never actually appears is because it defines 
 the constructors using operators rather than names, which is not allowed in 
 vanilla Haskell.  (There is an extension, TypeOperators, however, that does 
 allow this.)


 Nope: see Data.Complex.Complex; only infix *type* constructors are
nonstandard. The thing about lists that makes them impossible to
define in normal Haskell is the [a] syntax, which is some kind of
outfix type constructor, which no amount of currently available
extensions will allow. In addition, the constructor [] for the empty
list isn't a normal constructor, syntactically, because it doesn't
start with an uppercase character or a colon.

Basically, lists are so ubiquitous in Haskell that they have their own
special syntax, which cannot be defined like any other data type. It
is simple, as others have said, to define a new data type that works
identically to lists.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Definition of List type?

2010-07-30 Thread michael rice
Thanks all,

Now that I have a (very) rudimentary understanding of Haskell, I figured I'd 
back up and have a closer (conceptual) look at type definitions to see what 
they have in common, and just happen to pick Maybe and List.

I also noticed Maybe has a list of Instances

Monad Maybe
Functor Maybe
Typeable1 Maybe
MonadFix Maybe
MonadPlus Maybe
etc.

while List has none, at least I don't see any in Data.List. Same reason?

From Learn You A Haskell:

If a type is a part of a typeclass, that means it supports and implements the 
behavior the typeclass describes.

I'm way out on a limb here, but isn't Monad a typeclass? and if, as we say 
above, that Maybe is an instance of Monad, wouldn't there have to be

instance Monad Maybe where
 return = ...  -- return for Maybe
 = = ... -- bind for Maybe
 etc.

somewhere? Where? It's not in Data.Maybe. Is there some kind of scheme for 
defining this stuff, i.e., this goes here, that goes there?

Michael



--- On Fri, 7/30/10, Edward Z. Yang ezy...@mit.edu wrote:

From: Edward Z. Yang ezy...@mit.edu
Subject: Re: [Haskell-cafe] Definition of List type?
To: michael rice nowg...@yahoo.com, haskell-cafe 
haskell-cafe@haskell.org
Date: Friday, July 30, 2010, 3:01 PM

Excerpts from Edward Z. Yang's message of Fri Jul 30 14:48:34 -0400 2010:
     Const x xs  is x:xs (constructor)

That should be a Cons, not Const. :o)

Cheers,
Edward



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


[Haskell-cafe] using the orc library

2010-07-30 Thread Günther Schmidt

Hello,

I'd like to download 1,000 web pages with up to 6 six concurrent 
downloads at a time.


How can I express such a thread limit within the orc EDSL?

Günther

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


Re: [Haskell-cafe] Definition of List type?

2010-07-30 Thread Ben Millwood
On Fri, Jul 30, 2010 at 8:54 PM, michael rice nowg...@yahoo.com wrote:

 Thanks all,

 Now that I have a (very) rudimentary understanding of Haskell, I figured I'd 
 back up and have a closer (conceptual) look at type definitions to see what 
 they have in common, and just happen to pick Maybe and List.

 I also noticed Maybe has a list of Instances

 Monad Maybe
 Functor Maybe
 Typeable1 Maybe
 MonadFix Maybe
 MonadPlus Maybe
 etc.

 while List has none, at least I don't see any in Data.List. Same reason?

 From Learn You A Haskell:

 If a type is a part of a typeclass, that means it supports and implements 
 the behavior the typeclass describes.

 I'm way out on a limb here, but isn't Monad a typeclass? and if, as we say 
 above, that Maybe is an instance of Monad, wouldn't there have to be

 instance Monad Maybe where
  return = ...  -- return for Maybe
  = = ... -- bind for Maybe
  etc.

 somewhere? Where? It's not in Data.Maybe. Is there some kind of scheme for 
 defining this stuff, i.e., this goes here, that goes there?


It *is* in Data.Maybe:

http://hackage.haskell.org/packages/archive/base/4.2.0.1/doc/html/src/Data-Maybe.html

Generally speaking a type class instance should go either where the
type is defined, or where the class is defined, although there are
exceptions. In any case, if you can get the instance loaded in ghci,
you can find out where its defined:

ghci :i Maybe
data Maybe a = Nothing | Just a -- Defined in Data.Maybe
instance (Eq a) = Eq (Maybe a) -- Defined in Data.Maybe
instance Monad Maybe -- Defined in Data.Maybe
instance Functor Maybe -- Defined in Data.Maybe
instance (Ord a) = Ord (Maybe a) -- Defined in Data.Maybe
instance (Read a) = Read (Maybe a) -- Defined in GHC.Read
instance (Show a) = Show (Maybe a) -- Defined in GHC.Show
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Definition of List type?

2010-07-30 Thread Daniel Fischer
On Friday 30 July 2010 21:54:20, michael rice wrote:
 Thanks all,

 Now that I have a (very) rudimentary understanding of Haskell, I figured
 I'd back up and have a closer (conceptual) look at type definitions to
 see what they have in common, and just happen to pick Maybe and List.

 I also noticed Maybe has a list of Instances

 Monad Maybe
 Functor Maybe
 Typeable1 Maybe
 MonadFix Maybe
 MonadPlus Maybe
 etc.

 while List has none, at least I don't see any in Data.List. Same reason?

Data.List provides only functions for working with lists, while Data.Maybe 
also contains the definition of the type.

Type class instances are documented
- at the type class
- at the data type

Since the list datatype isn't documented like the other types (probably 
because it's not defined in valid Haskell but built-in), the list instances 
appear only at the type classes (and at the Monad documentation, you find 
Monad [] listed as the first instance.


 From Learn You A Haskell:

 If a type is a part of a typeclass, that means it supports and
 implements the behavior the typeclass describes.

 I'm way out on a limb here, but isn't Monad a typeclass?

Yes.

 and if, as we
 say above, that Maybe is an instance of Monad, wouldn't there have to be

 instance Monad Maybe where
  return = ...  -- return for Maybe
  = = ... -- bind for Maybe
  etc.

 somewhere?

Yes, there is. In GHC at least, it's defined in Data.Maybe:

instance  Monad Maybe  where
(Just x) = k  = k x
Nothing  = _  = Nothing

(Just _)   k  = k
Nothing_  = Nothing

return  = Just
fail _  = Nothing



 Where? It's not in Data.Maybe. Is there some kind of scheme
 for defining this stuff, i.e., this goes here, that goes there?

Instance declarations should be in the same module where
- the class is defined, or
- the type is defined
if possible.

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


[Haskell-cafe] Problem with haskell types

2010-07-30 Thread Anupam Jain
Hi,

I am having trouble getting a small program to compile. The helpful folks at
#haskell created a version of the program that does compile -
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=28406#a28408 but it is not
very clear to them (and to me) why the original program wouldn't type
compile in the first place.

Here's the program that refuses to compile -

module Delme () wheredata DecisionState = A | B | C | Dd_test :: Eq b
= b - b - DecisionState - DecisionState - ()d_test test testVal
trueState falseState =if (test == testVal) then d trueState
 else d falseStated :: DecisionState - ()d A = d_test True True B Cd
B = d_test 1 2 C Dd C = d_test True False A Bd D = ()

I get an error like -

Delme.hs:13:0:
Contexts differ in length
  (Use -XRelaxedPolyRec to allow this)
When matching the contexts of the signatures for
  d_test :: forall b.
(Eq b) =
b - b - DecisionState - DecisionState - ()
  d :: DecisionState - ()
The signature contexts in a mutually recursive group should all be
identical
When generalising the type(s) for d_test, d

Putting in the extension does get the program to type check but the original
program should have type compiled in the first place.

The ironic thing we discovered is that if we remove the type declaration for
'd', the program type checks, and GHC then derives the exact same type which
we removed!

Can some of the smarter people in the room please shed more light on this?

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


[Haskell-cafe] Announce type-level-natural-number-1.0: Simple, Haskell 2010-compatible type level natural numbers

2010-07-30 Thread Gregory Crosswhite
 Hey everyone,

I am pleased to announce the release of the type-level-natural-number
package, which implements natural numbers at the type level.  Although
there are many packages on Hackage that implement type level natural
numbers, this package is distinguished by its simplicity: it does not
offer any operations other than predecessor, successor, and conversion
to Int, and so the only Haskell extension it needs is EmptyDataDecls. 
Thus, this package is compatible with Haskell 2010.

The envisioned use case is for annotating types with natural numbers, so
that extra functionality such as addition and subtraction of natural
numbers is unnecessary.  Nothing is stopping someone from implementing
this functionality, and in fact I may do so myself;  however, since such
functionality is not needed merely for using these numbers, I decided to
leave it out in order to avoid having to use non-Haskell 2010 extensions
(especially UndecidableInstances).  In particular, a major motivation
behind designing the package in this way is to make it more appealing as
a standard means for representing natural number annotations in order to
promote interoperability between libraries.

I welcome any feedback that the community has to offer.

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


Re: [Haskell-cafe] Definition of List type?

2010-07-30 Thread michael rice
Hi Daniel,

OK, now I'm getting somewhere. I was looking here:

http://haskell.org/ghc/docs/6.12.1/html/libraries/base-4.2.0.0/Data-Maybe.html

instead of in the source.

Seem to be on the right track. I'm going to do some more poking around.

Thanks a lot, guys.

Michael


--- On Fri, 7/30/10, Daniel Fischer daniel.is.fisc...@web.de wrote:

From: Daniel Fischer daniel.is.fisc...@web.de
Subject: Re: [Haskell-cafe] Definition of List type?
To: haskell-cafe@haskell.org
Cc: michael rice nowg...@yahoo.com
Date: Friday, July 30, 2010, 4:23 PM

On Friday 30 July 2010 21:54:20, michael rice wrote:
 Thanks all,

 Now that I have a (very) rudimentary understanding of Haskell, I figured
 I'd back up and have a closer (conceptual) look at type definitions to
 see what they have in common, and just happen to pick Maybe and List.

 I also noticed Maybe has a list of Instances

 Monad Maybe
 Functor Maybe
 Typeable1 Maybe
 MonadFix Maybe
 MonadPlus Maybe
 etc.

 while List has none, at least I don't see any in Data.List. Same reason?

Data.List provides only functions for working with lists, while Data.Maybe 
also contains the definition of the type.

Type class instances are documented
- at the type class
- at the data type

Since the list datatype isn't documented like the other types (probably 
because it's not defined in valid Haskell but built-in), the list instances 
appear only at the type classes (and at the Monad documentation, you find 
Monad [] listed as the first instance.


 From Learn You A Haskell:

 If a type is a part of a typeclass, that means it supports and
 implements the behavior the typeclass describes.

 I'm way out on a limb here, but isn't Monad a typeclass?

Yes.

 and if, as we
 say above, that Maybe is an instance of Monad, wouldn't there have to be

 instance Monad Maybe where
  return = ...  -- return for Maybe
  = = ... -- bind for Maybe
  etc.

 somewhere?

Yes, there is. In GHC at least, it's defined in Data.Maybe:

instance  Monad Maybe  where
    (Just x) = k      = k x
    Nothing  = _      = Nothing

    (Just _)   k      = k
    Nothing    _      = Nothing

    return              = Just
    fail _              = Nothing



 Where? It's not in Data.Maybe. Is there some kind of scheme
 for defining this stuff, i.e., this goes here, that goes there?

Instance declarations should be in the same module where
- the class is defined, or
- the type is defined
if possible.




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


Re: [Haskell-cafe] Problem with haskell types

2010-07-30 Thread roconnor

I was one of the people on #haskell discussing this with Anupam.

Note that that when you remove the signature of d, the result complies and 
ghci will state the inferred type of d is exactly the signature that you 
are not allowed to write.


In my opinion, this is a bug in the Haskell 98 report where it says

``If the programmer supplies explicit type signatures for more than one 
variable in a declaration group, the contexts of these signatures must be 
identical up to renaming of the type variables.


The problem is that we cannot give a type signature to d with exactly the 
constraints of d_test because d doesn't have any type variable in its type 
signature.


At the very least the Haskell report should allow type checking to proceed 
if everything in a declaration group has a signature even if the 
signatures don't have identical constraints.


A trac ticket is needed for Haskell 2011, if one doesn't already exist.

On Sat, 31 Jul 2010, Anupam Jain wrote:


Hi,
I am having trouble getting a small program to compile. The helpful folks at 
#haskell created a version of the
program that does compile 
- http://hpaste.org/fastcgi/hpaste.fcgi/view?id=28406#a28408 but it is not very 
clear
to them (and to me) why the original program wouldn't type compile in the first 
place.

Here's the program that refuses to compile -

module Delme () where

data DecisionState = A | B | C | D

d_test :: Eq b = b - b - DecisionState - DecisionState - ()
d_test test testVal trueState falseState =
if (test == testVal)
 then d trueState
 else d falseState

d :: DecisionState - ()
d A = d_test True True B C
d B = d_test 1 2 C D
d C = d_test True False A B
d D = ()
I get an error like -

Delme.hs:13:0:
    Contexts differ in length
      (Use -XRelaxedPolyRec to allow this)
    When matching the contexts of the signatures for
      d_test :: forall b.
                (Eq b) =
                b - b - DecisionState - DecisionState - ()
      d :: DecisionState - ()
    The signature contexts in a mutually recursive group should all be identical
    When generalising the type(s) for d_test, d

Putting in the extension does get the program to type check but the original 
program should have type compiled
in the first place.

The ironic thing we discovered is that if we remove the type declaration for 
'd', the program type checks, and
GHC then derives the exact same type which we removed!

Can some of the smarter people in the room please shed more light on this?

-- Anupam





--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Announce type-level-natural-number-1.0: Simple, Haskell 2010-compatible type level natural numbers

2010-07-30 Thread Alexey Khudyakov
On Fri, 30 Jul 2010 13:28:19 -0700
Gregory Crosswhite gcr...@phys.washington.edu wrote:
  Hey everyone,
 
 I am pleased to announce the release of the type-level-natural-number
 package, which implements natural numbers at the type level.  Although
 there are many packages on Hackage that implement type level natural
 numbers, this package is distinguished by its simplicity: it does not
 offer any operations other than predecessor, successor, and conversion
 to Int, and so the only Haskell extension it needs is EmptyDataDecls. 
 Thus, this package is compatible with Haskell 2010.
 
 The envisioned use case is for annotating types with natural numbers, so
 that extra functionality such as addition and subtraction of natural
 numbers is unnecessary.  Nothing is stopping someone from implementing
 this functionality, and in fact I may do so myself;  however, since such
 functionality is not needed merely for using these numbers, I decided to
 leave it out in order to avoid having to use non-Haskell 2010 extensions
 (especially UndecidableInstances).  In particular, a major motivation
 behind designing the package in this way is to make it more appealing as
 a standard means for representing natural number annotations in order to
 promote interoperability between libraries.
 
Type level addition doesn't require UndecidableInstances. It only
require TypeFamilies or fundeps. Here is implementation using type
families:

 type family Add n m :: *

 type instance Add Zero  Zero   = Zero
 type instance Add Zero (SuccessorTo n) = SuccessorTo n
 type instance Add (SuccessorTo n) m= SuccessorTo (Add n m)

Standard package is could be somewhat difficult. Standards are
undeniably good but one size doesn't fit all rule does apply here.
Your package couldn't be used to represent big numbers. Little real
work has been done on this so it's reasonable to expect progress or
even some breakthough. 

Maybe some generic inteface for conversion of different representation
of natural numbers would be good. Any suggestions

-- 
Alexey Khudyakov alexey.sklad...@gmail.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Can we come out of a monad?

2010-07-30 Thread Alexey Khudyakov
On Fri, 30 Jul 2010 09:29:59 +0200
Stefan Holdermans ste...@vectorfabrics.com wrote:

 Jason,
 
  There is one case where you can break out of a monad without knowing which
  monad it is.  Well, kind of.  It's cheating in a way because it does force
  the use of the Identity monad.  Even if it's cheating, it's still very
  clever and interesting.
 
 How is this cheating?  Or better, how is this breaking out of a monad without
 knowing which monad it is?  It isn't. You know exactly which monad you're
 breaking out: it's the identity monad.  That's what happens if you put
 quantifiers in negative positions: here, you are not escaping out of an
 arbitrary monad (which you can't), but escaping out of a very specific monad.
 
No I think here we breaking out from _arbitrary_ monad. If monadic
function works for every monad then it must work for identity monad
too. Here is simplest form of purify function:

 purify2 :: (forall m . Monad m = m a) - a
 purify2 m = runIdentity m

This proves interesting fact. Value could be removed from monad if no
constrain is put on the type of monad. Moreover it Monad in this
example could be replaced with Functor or other type class

I wonder could this function be written without resorting to concrete
monad


-- 
Alexey Khudyakov alexey.sklad...@gmail.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] using the orc library

2010-07-30 Thread Edward Z. Yang
Excerpts from Günther Schmidt's message of Fri Jul 30 16:16:38 -0400 2010:
 I'd like to download 1,000 web pages with up to 6 six concurrent 
 downloads at a time.
 
 How can I express such a thread limit within the orc EDSL?

One solution that comes to mind is place all 1000 web pages in an MVar
containing a queue of URLs to process (a list will probably suffice),
and then use Orc to orchestrate six threads that pull a page from the queue
and make a download.  Admittedly, Orc doesn't buy you very much in this
scenario until you add timeout handling and such.

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


[Haskell-cafe] Microsoft's Singularity Project and Haskell

2010-07-30 Thread Vasili I. Galchin
Hello,

In the latest ACM CACM is a paper on Singularity. Here also is an
overview: http://lambda-the-ultimate.org/node/1081. I haven't finished the
CACM paper yet but I only mention of languages like C# and F#. Singularity
is predicated around providing a safe
environment. IMO Haskell is even better than their languages. My $.02.

Regards,

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


Re: [Haskell-cafe] Announce type-level-natural-number-1.0: Simple, Haskell 2010-compatible type level natural numbers

2010-07-30 Thread John Meacham
On Sat, Jul 31, 2010 at 01:32:50AM +0400, Alexey Khudyakov wrote:
  The envisioned use case is for annotating types with natural numbers, so
  that extra functionality such as addition and subtraction of natural
  numbers is unnecessary.  Nothing is stopping someone from implementing
  this functionality, and in fact I may do so myself;  however, since such
  functionality is not needed merely for using these numbers, I decided to
  leave it out in order to avoid having to use non-Haskell 2010 extensions
  (especially UndecidableInstances).  In particular, a major motivation
  behind designing the package in this way is to make it more appealing as
  a standard means for representing natural number annotations in order to
  promote interoperability between libraries.
  
 Type level addition doesn't require UndecidableInstances. It only
 require TypeFamilies or fundeps. Here is implementation using type
 families:

FunDeps also require MPTCs. I am becoming a huge fan of type
families/associated types. There is a fairly good chance jhc will
support them well before or even instead of MPTCs.


  type family Add n m :: *
 
  type instance Add Zero  Zero   = Zero
  type instance Add Zero (SuccessorTo n) = SuccessorTo n
  type instance Add (SuccessorTo n) m= SuccessorTo (Add n m)
 
 Standard package is could be somewhat difficult. Standards are
 undeniably good but one size doesn't fit all rule does apply here.
 Your package couldn't be used to represent big numbers. Little real
 work has been done on this so it's reasonable to expect progress or
 even some breakthough. 

I thought there was some elegant way to express type level numbers
using balanced ternary, but I can't find a reference to it at the
moment.


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] Can we come out of a monad?

2010-07-30 Thread John Meacham
On Sat, Jul 31, 2010 at 01:49:43AM +0400, Alexey Khudyakov wrote:
 No I think here we breaking out from _arbitrary_ monad. If monadic
 function works for every monad then it must work for identity monad
 too. Here is simplest form of purify function:
 
  purify2 :: (forall m . Monad m = m a) - a
  purify2 m = runIdentity m
 
 This proves interesting fact. Value could be removed from monad if no
 constrain is put on the type of monad. Moreover it Monad in this
 example could be replaced with Functor or other type class

This becomes much more clear when you float the quantifier to the top
level: 

 purify2 :: (forall m . Monad m = m a) - a

since the quantifier is in an argument position, to float it out, we
need to flip it, it goes from universal to existential quantification.
so we get the equivalent type:

 purify2' :: exists m . Monad m = (m a - a)

which you can read as there exists some monad for which you can pull
out its value. The implementation is just the witness that proves that
Identity is one such monad, satisfying the existential quantification.

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] Re: Re: Can we come out of a monad?

2010-07-30 Thread John Meacham
On Fri, Jul 30, 2010 at 11:57:00AM -0500, Jason Catena wrote:
 By this example State doesn't seem to give you anything more than a
 closure would, since it doesn't act like much of an accumulator (by,
 for example, storing 6 as its new internal value).
 
 Could you use State for something like storing the latest two values
 of a Fibonacci series?  For example, each time you call it, it
 generates the next term, discards the oldest term, and stores the
 newly-generated term?

Although state can't be used to calculate things that couldn't be
calculated otherwise, it can be used to implement things faster (in a
real, computer theoretic sense) than they could be otherwise. For
instance, the union-find algorithm cannot be implemented efficiently
without state, the state monad allows the best of both worlds, a pure
interface but the fast algorithm under the hood.

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] Problem with haskell types

2010-07-30 Thread Job Vranish
Yeah I recently ran into this myself. (
http://osdir.com/ml/haskell-cafe@haskell.org/2010-07/msg00020.html). It's
not a bug, just a limitation of haskell's inference algorithm for mutually
recursive groups of functions.

The problem is that haskell infers groups (the strongly connected
components) of mutually recursive functions monomorphically. This means that
all uses of the function in the group, and the definition, must all have the
same type. In haskell 98, there was no way to get around this (not even
with explicit type signatures), hence the rule that Russell pointed out in
haskell 98 report:
``If the programmer supplies explicit type signatures for more than one
variable in a declaration group, the contexts of these signatures must be
identical up to renaming of the type variables.
There was no meaningful way for this not be to be case with the old haskell
98 rules (since inferring such types was impossible).

However,

Most implementations of haskell now have a (non Haskell 98 compliant) rule
that breaks a function out of a mutually recursive group if it already has a
type signature. Usually GHC requires the explicit enabling of extensions
when functionality breaks with the haskell 98 standard, but in this case it
lets you get away with it. However, GHC _does_ require the RelaxedPolyRec
extension if you want to specify different contexts on your mutually
recursive function group.

I imaging this is mostly just because allowing it without
the extension would be contradicting an explicit rule in the haskell 98
standard. But there might be some monomorphism restriction like performance
issues with it too, I'm not sure.


There has also been some work on alternative algorithms that solve this
problem without the need for explicit type signatures. The mercury language
supports full polymorphic recursion. And there is a paper on a better
algorithm, that could potentially be used by haskell, here:
http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.98.4930

Phew, I think I got that all right, though I just learned this stuff myself
only a month ago, so I'm mostly just passing it on :)
Hope that helps clear things up :)

- Job

On Fri, Jul 30, 2010 at 5:34 PM, rocon...@theorem.ca wrote:

 I was one of the people on #haskell discussing this with Anupam.

 Note that that when you remove the signature of d, the result complies and
 ghci will state the inferred type of d is exactly the signature that you are
 not allowed to write.

 In my opinion, this is a bug in the Haskell 98 report where it says

 ``If the programmer supplies explicit type signatures for more than one
 variable in a declaration group, the contexts of these signatures must be
 identical up to renaming of the type variables.

 The problem is that we cannot give a type signature to d with exactly the
 constraints of d_test because d doesn't have any type variable in its type
 signature.

 At the very least the Haskell report should allow type checking to proceed
 if everything in a declaration group has a signature even if the signatures
 don't have identical constraints.

 A trac ticket is needed for Haskell 2011, if one doesn't already exist.


 On Sat, 31 Jul 2010, Anupam Jain wrote:

  Hi,
 I am having trouble getting a small program to compile. The helpful folks
 at #haskell created a version of the
 program that does compile -
 http://hpaste.org/fastcgi/hpaste.fcgi/view?id=28406#a28408 but it is not
 very clear
 to them (and to me) why the original program wouldn't type compile in the
 first place.

 Here's the program that refuses to compile -

 module Delme () where

 data DecisionState = A | B | C | D

 d_test :: Eq b = b - b - DecisionState - DecisionState - ()
 d_test test testVal trueState falseState =
if (test == testVal)
 then d trueState
 else d falseState

 d :: DecisionState - ()
 d A = d_test True True B C
 d B = d_test 1 2 C D
 d C = d_test True False A B
 d D = ()
 I get an error like -

 Delme.hs:13:0:
 Contexts differ in length
   (Use -XRelaxedPolyRec to allow this)
 When matching the contexts of the signatures for
   d_test :: forall b.
 (Eq b) =
 b - b - DecisionState - DecisionState - ()
   d :: DecisionState - ()
 The signature contexts in a mutually recursive group should all be
 identical
 When generalising the type(s) for d_test, d

 Putting in the extension does get the program to type check but the
 original program should have type compiled
 in the first place.

 The ironic thing we discovered is that if we remove the type declaration
 for 'd', the program type checks, and
 GHC then derives the exact same type which we removed!

 Can some of the smarter people in the room please shed more light on this?

 -- Anupam




 --
 Russell O'Connor  http://r6.ca/
 ``All talk about `theft,''' the general counsel of the American Graphophone
 Company wrote, ``is the merest claptrap, for there exists no 

Re: [Haskell-cafe] Announce type-level-natural-number-1.0: Simple, Haskell 2010-compatible type level natural numbers

2010-07-30 Thread John Meacham
Heh. I was just thinking I needed type level naturals last night at the
pub. I wanted to support gcc's vector type extension in jhc

http://gcc.gnu.org/onlinedocs/gcc/Vector-Extensions.html

which allow diretly expressing vector operations that use the SIMD
features of modern CPUS, I didn't want to pre-create every possible
choice so encoding the size as a type level number makes sense.

I support complex numbers via a similar higher order type,

 data Complex_ :: # - #

then I can use 'Complex_ Float64_' to get unboxed complex doubles.


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] Can we come out of a monad?

2010-07-30 Thread wren ng thornton

Tillmann Rendel wrote:

C K Kashyap wrote:

I am of the
understanding that once you into a monad, you cant get out of it? 


That's not correct.


Indeed. The correct formulation of the statement is that it's not safe 
to leave a monad. Where safe has the same connotation as in all the 
unsafeFoo functions--- namely, you have additional proof obligations.


In other words, there is no general function:

escape :: forall a m. (Monad m) = m a - a

Or any variant that takes additional arguments of a fixed type. But 
really, the nonexistence of this function is the only claim we're making 
about it not being safe to escape a monad. It's certainly true that we 
can exit a monad (provided the additional proof/arguments necessary for 
the particular monad in question). Indeed, almost every monad can be 
exited. The tricky bit is, they all require some *different* kind of 
proof, so we can't write a general version that works for every monad.


For example, in the Maybe monad we will either have an A, or we will 
not. So how can we extract an A? Well, if the monadic value is Just a, 
then we can use pattern matching to extract the A. But if the monadic 
value is Nothing, then what? Well, in order to provide an A, we'll need 
to have some default A to provide when the Maybe A doesn't contain one. 
So this default A is our proof of safety for exiting Maybe:


exitMaybe :: forall a. a - Maybe a - a
exitMaybe default Nothing = default
exitMaybe _ (Just something) = something

For another example, in the list monad we will have zero or more A. So 
how can we return an A? Here we have a number of options. We could write 
a function similar to exitMaybe, where we select some value in the list 
arbitrarily or else return the default value if the list is empty. This 
would match the idea that the list monad encapsulates nondeterministic 
computations. But we loose some information here. Namely, why are we 
carrying this list of all possible values around when we're just going 
to select one arbitrarily? Why not select it earlier and save ourselves 
some baggage? The idea of using a list as nondeterminism means that we 
want to know *all* possible values our nondeterministic machine could 
return. In that case, we need some way of combining different A values 
in order to get an aggregate value as our output. Thus,


exitList :: forall a. a - (a - a - a) - [a] - a
exitList x f [] = x
exitList x f (a:as) = f a (exitList x f as)

Of course we could also implement different versions for returning the 
elements of the list in a different order. And if we wanted to be more 
general we could allow the type of x and the return type of f to be any 
arbitrary type B. Here, our proof is the two arguments for eliminating 
a list.


The reason IO is special is, what kind of proof do we require in order 
to exit the IO monad and return a pure result? Ah, that's a tricky one 
isn't it. This really comes down to asking what the meaning of the IO 
monad really is; if we knew what kind of structure IO has, then we could 
derive a way of deconstructing that structure, just like we did for list 
and Maybe. Because it includes disk access, in order to exit the IO 
monad in general we would need (among other things) to be able to 
predict/provide the values of all files, including ones got via the 
network, and default values for all disk or network failures. Actually, 
we need those proofs for every moment in time, because IO is volatile 
and someone might do something like enter a loop trying to read a file 
over and over again until it finally succeeds.


Clearly we cannot provide those kinds of proof in practice. They'd be 
too big! Actually, this bigness might even be a theoretical problem 
since the program has to fit in a file on disk, but the program must 
include (some non-IO way of getting) the values of all the files on the 
disk or the network. So we cannot exit the IO monad in general. But IO 
is a sin bin that does a lot of other stuff too, like give reflection on 
the state of the runtime system. It's perfectly possible to write an 
adaptive algorithm that does things quickly when it has access to lots 
of memory, but does things more optimally when memory is constrained. 
Provided it gives the same answers regardless of resources, then it's 
perfectly safe and referentially transparent to run this algorithm to 
return a pure value, despite it using IO operations to monitor how much 
memory is free while it runs. Things like this are what unsafePerformIO 
is for. In order to use that function we must still provide proof that 
it's safe to exit the monad, only this time it's not a token that's 
passed around within the code, it's an actual proof that we've 
demonstrated in some theoretical framework for reasoning about Haskell.


...

For what it's worth, this situation is reversed for comonads. Monads, 
which represent a kind of structure-around-values, can be freely entered 
with return (by giving 

Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread wren ng thornton

Ivan Lazar Miljenovic wrote:

More and more people seem to be getting away from trying to say that
monads are containers/burritos/etc. and just teaching them by way of the
definition, either = and return or just join


You always need return. The choice of primitives is:

return, (=)

or:

fmap, return, join

--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] dear traversable

2010-07-30 Thread Ben
dear traversable geniuses --

i am looking for better implementations of

unzipMap :: M.Map a (b, c) - (M.Map a b, M.Map a c)
unzipMap m = (M.map fst m, M.map snd m)

unliftMap :: (Ord a) = M.Map a (b - c) - M.Map a b - M.Map a c
unliftMap mf ma = M.mapWithKey (\k v - mf M.! k $ v) ma

the first is obviously inefficient as it traverses the map twice.  the
second just seems like it is some kind of fmap.

any ideas?

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


Re: [Haskell-cafe] Can we come out of a monad?

2010-07-30 Thread wren ng thornton

Martijn van Steenbergen wrote:
In fact, I would argue that a monad which you cannot escape from is not 
very useful at all. IO is the only exception I know of.


You can escape IO just fine. Just compile your program, and then run it 
in the real life monad. Results aren't guaranteed to be the same across 
all runs, but that's the whole reason for using monads to reason purely 
about side effects.


Eh? You meant while staying within the computer?

--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] dear traversable

2010-07-30 Thread John Meacham
On Fri, Jul 30, 2010 at 08:13:43PM -0700, Ben wrote:
 unliftMap :: (Ord a) = M.Map a (b - c) - M.Map a b - M.Map a c
 unliftMap mf ma = M.mapWithKey (\k v - mf M.! k $ v) ma

I always thought a useful map primitive would be

unionWithJoin 
   :: (a - b - c)  -- combine values that appear in both maps
   - (b - c)   -- value appears in second map but not the first
   - (a - c)   -- value appears in first map but not second
   - Map k a - Map k b - Map k c

along with the 'WithKey' and 'Maybe' variants.


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] Can we come out of a monad?

2010-07-30 Thread wren ng thornton

Alex Rozenshteyn wrote:

I also found myself thinking about list as a monad in terms of this
discussion.  I think it's an interesting case:  it's pure, but it doesn't
really make sense to come out of it.  Head, indexing, and last all break
out of it, but none of them can be the default, and all of them require you
to consider it as something more than its monad-ness.


The proper monad for nondeterminism is a set of values. If we think of 
the machine as a nondeterministic automaton, then this set is the set of 
current states in the machine. The bind operation represents taking a 
step (or multiple steps) in the automaton.


If we generalize this to a weighted set then we get a distribution 
monad. This corresponds to current states in a weighted nondeterministic 
automaton. In the limit case our weights are unit, in which case this is 
isomorphic to the nondeterminism monad. The next interesting step is 
discrete weights (which, in this case, is isomorphic to using a 
multiset), corresponding to counts of current positions in a 
nondeterministic automaton. If we allow continuous weights, then this 
brings us over towards probability theory, hence calling it the 
distribution monad.


If we generalize this to a (weighted) set of values annotated by the 
history of choices leading to their derivation, then we would get a 
path/proof (distribution) monad. This corresponds to the current set of 
(weighted) *paths* through a (weighted) nondeterministic automaton. The 
bind operation represents extending the paths. If we erase the histories 
in the set, then we get a multiset of values, which is why this is 
different from the distribution monad. Generalizing this further, We can 
also think of proof theoretic systems as automata which allow hyperarcs 
(i.e., arrows with multiple inputs). In this case, the histories in the 
path monad become trees instead of just linear chains. These histories 
are the proof trees for their values.


...

All of these monads have natural ways of exiting them. Set-theoretic 
operations generally make sense as corresponding operations on the 
underlying automata, though there may be a few that don't. 
Unfortunately, the list monad isn't any of these. It's closest to the 
distribution monad with discrete weights, since lists are close to 
multisets. However, lists have additional structure, namely they are 
ordered multisets (not ordered weighted sets), and the ordering has 
nothing to do with the type of the values. This ordering is why they 
have so many other weird ways of being manipulated. While lists form a 
perfectly good monad, they don't have any clean and elegant translation 
into automata theory that I can think of.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread wren ng thornton

Brandon S Allbery KF8NH wrote:

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 7/30/10 11:48 , Ivan Lazar Miljenovic wrote:

Ertugrul Soeylemez e...@ertes.de writes:

it's a bit hidden in Haskell, but a monad instance consists of three
functions:

  fmap   :: (a - b) - (m a - m b)

You don't even need fmap defined for it to be a monad, since fmap f m =
liftM f m = m = (return . f)


fmap/join and return/bind are isomorphic; given either set, you can produce
the other.


No. fmap+join is isomorphic to bind. Your options are (fmap,return,join) 
or (return,bind). There is no way to get by without the return, since 
that's the natural transformation necessary for entering the monad in 
the first place.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Re: Can we come out of a monad?

2010-07-30 Thread wren ng thornton

Jason Catena wrote:

By this example State doesn't seem to give you anything more than a
closure would, since it doesn't act like much of an accumulator (by,
for example, storing 6 as its new internal value).


Reader r = (r-)
Writer m = Monoid m = (m,)
State  s = (s-) . (s,)

So, yes, the state monad can change the internal value.


Could you use State for something like storing the latest two values
of a Fibonacci series?


Sure. let s = (Int,Int) and

fibs = start
where
start 0 = 0
start 1 = 1
start n = evalState (recurse $! n-2) (0,1)

recurse n = do
(x,y) - get
let z = x+y
z `seq` if n==0
then return z
else do
put (y,z)
recurse $! n-1

will return the nth Fibonacci number, with memoization, while only 
holding onto the previous two memos.




Would Haskell memoize already-generated values in either case?


No. Doing so would lead to enormous memory leaks.


Could
we write a general memoizer across both the recursive and State
implementations, or must we write a specific one to each case?


There are a number of generic memoization libraries on Hackage, just 
take a look.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Definition of List type?

2010-07-30 Thread wren ng thornton

Ben Millwood wrote:

On Fri, Jul 30, 2010 at 7:50 PM, Gregory Crosswhite
gcr...@phys.washington.edu wrote:

The reason why this definition never actually appears is because it defines the 
constructors using operators rather than names, which is not allowed in vanilla 
Haskell.  (There is an extension, TypeOperators, however, that does allow this.)



 Nope: see Data.Complex.Complex; only infix *type* constructors are
nonstandard. The thing about lists that makes them impossible to
define in normal Haskell is the [a] syntax, which is some kind of
outfix type constructor, which no amount of currently available
extensions will allow.


It's normally called confix or circumfix.

Similarly, the tuple syntaxes can't be defined in Haskell because they 
use mixfix notation (which apparently some folks call distfix[1]). 
Also, lists support a mixfix sugar where [a,b,...,c] = a:b:...:c:[]


Agda does support full mixfix notation. While it's nice in theory, when 
combined with the verbosity of dependently typed languages it gets 
illegible pretty quickly for the uninitiated.



[1] http://github.com/noteed/syntactical

--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Microsoft's Singularity Project and Haskell

2010-07-30 Thread Vasili I. Galchin
Probably a more poignant question would be a comparison of Haskell's type
system and Sing#'s (http://en.wikipedia.org/wiki/Sing_sharp).

Vasili

On Fri, Jul 30, 2010 at 5:19 PM, Vasili I. Galchin vigalc...@gmail.comwrote:

 Hello,

 In the latest ACM CACM is a paper on Singularity. Here also is an
 overview: http://lambda-the-ultimate.org/node/1081. I haven't finished the
 CACM paper yet but I only mention of languages like C# and F#. Singularity
 is predicated around providing a safe
 environment. IMO Haskell is even better than their languages. My $.02.

 Regards,

 Vasili



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


Re: [Haskell-cafe] dear traversable

2010-07-30 Thread wren ng thornton

Ben wrote:

unliftMap :: (Ord a) = M.Map a (b - c) - M.Map a b - M.Map a c
unliftMap mf ma = M.mapWithKey (\k v - mf M.! k $ v) ma

the first is obviously inefficient as it traverses the map twice.  the
second just seems like it is some kind of fmap.


It's the (*) operator of Applicative, which is equivalent to `ap` on 
Monad (though (*) may be more efficient for certain monads). Or 
rather, it *should* be the (*) operator. The use of (!) means it will 
explode when when the keys of ma are not a subset of the keys of mf. 
Really, it should be


apMap mf ma = M.mapMaybeWithKey (\k f - f $ M.lookup k ma) mf

Though that's not any more efficient. It will be somewhat slower because 
of the need to remove the spine for deleted elements, but the difference 
should be marginal.


The similarity between (*) and fmap aka ($) is certainly notable. 
However, they are quite distinct:


($) :: Functor f =   (a -   b) - f a - f b
(*) :: Applicative f = f (a -   b) - f a - f b
(=) :: Monad   f =   (a - f b) - f a - f b

Each one gives more power than the previous because it can accept 
functions with more structure. I.e. fmap doesn't allow any structure; 
(*) allows top-level structure and so it must be able to perform a 
sort of multiplication (e.g., intersection or cross-product) on 
f-structures; and (=) allows embedded structure, and so it must be 
able to perform a kind of extension (e.g., the multiplication of a 
semiring) on f-structures.


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] dear traversable

2010-07-30 Thread wren ng thornton

Ben wrote:

dear traversable geniuses --

i am looking for better implementations of

unzipMap :: M.Map a (b, c) - (M.Map a b, M.Map a c)
unzipMap m = (M.map fst m, M.map snd m)


I don't think you can give a more efficient implementation using the 
public interface of Data.Map. You need to have a sort of mapping 
function that allows you to thread them together, either via 
continuations or via a primitive:


splitMap :: (a - (b,c)) - Map k a - (Map k b, Map k c)

This splitMap and the mapEither primitive could be combined:

data Or a b = Fst a | Both a b | Snd b

eitherOr (Left  a) = Fst a
eitherOr (Right b) = Snd a

mapOr :: (a - Or b c) - Map k a - (Map k b, Map k c)

mapEither f = mapOr (eitherOr . f)
splitMap  f = mapOr (uncurry Both)

And the type of John's primitive could be prettied up:

unionWithJoin :: (Or a b - c) - Map k a - Map k b - Map k c

--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Can we come out of a monad?

2010-07-30 Thread Stefan Holdermans
Alexey,

 There is one case where you can break out of a monad without knowing which
 monad it is.  Well, kind of.  It's cheating in a way because it does force
 the use of the Identity monad.  Even if it's cheating, it's still very
 clever and interesting.
 
 How is this cheating?  Or better, how is this breaking out of a monad 
 without
 knowing which monad it is?  It isn't. You know exactly which monad you're
 breaking out: it's the identity monad.  That's what happens if you put
 quantifiers in negative positions: here, you are not escaping out of an
 arbitrary monad (which you can't), but escaping out of a very specific monad.
 
 No I think here we breaking out from _arbitrary_ monad. If monadic
 function works for every monad then it must work for identity monad
 too.

Once, again: no. :)  You're not escaping from an arbitrary monad; you are 
escaping from the identity monad.

 purify2 :: (forall m . Monad m = m a) - a
 purify2 m = runIdentity m

The function you pass into purify2 works for an arbitrary monad.  Purify itself 
instantiates this function to the identify monad—and then escapes from it.

My former boss used to tell me that these are the kinds of things you should 
try to explain yourself while riding you're bike.  If longer you ride your 
bike, the better you'll understand it.

Have fun biking ;-),

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