[Haskell-cafe] OFX libs available ?

2009-04-09 Thread Simon Michael

Has anyone got code for OFX financial data handling they could share ?

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


[Haskell-cafe] Ambiguous reified dictionaries

2009-04-09 Thread Martijn van Steenbergen

Good morning,

The [1]GHC user's guide, section 8.4.5 says:

"The new feature is that pattern-matching on MkSet (as in the definition 
of insert) makes available an (Eq a) context. In implementation terms, 
the MkSet constructor has a hidden field that stores the (Eq a) 
dictionary that is passed to MkSet; so when pattern-matching that 
dictionary becomes available for the right-hand side of the match."


But what happens if there are several dictionaries available?

Consider these three modules:

ReifyMonoid.hs:


{-# LANGUAGE GADTs #-}

module ReifyMonoid where

import Data.Monoid

data MonoidInst a where
  MkMonoidInst :: Monoid a => MonoidInst a


ReifySum.hs:


module ReifySum where

import ReifyMonoid
import Data.Monoid

instance Monoid Int where
  mempty = 0
  mappend = (+)

intSum :: MonoidInst Int
intSum = MkMonoidInst


ReifyProd.hs:


module ReifyProd where

import ReifyMonoid
import Data.Monoid

instance Monoid Int where
  mempty = 1
  mappend = (*)

intProd :: MonoidInst Int
intProd = MkMonoidInst


Now a function


emp :: MonoidInst a -> a
emp MkMonoidInst = mempty


works as you'd expect:

*ReifySum ReifyProd> emp intSum
0
*ReifySum ReifyProd> emp intProd
1

But what about this function?


empAmb :: MonoidInst a -> MonoidInst a -> a
empAmb MkMonoidInst MkMonoidInst = mempty


Now there are two dictionaries available. GHC consistently picks the one 
from the second argument:


*ReifySum ReifyProd> empAmb intProd intSum
1
*ReifySum ReifyProd> empAmb intSum intProd
0

My questions are:

1) Shouldn't GHC reject this as being ambiguous?
2) Should class constraints only be available on existentially qualified 
type variables to prevent this from happening at all?

3) Is it possible to implement the following function?


mkMonoidInst :: a -> (a -> a -> a) -> MonoidInst a
mkMonoidInst mempty mappend = ...


Thank you,

Martijn.



[1] 
http://www.haskell.org/ghc/docs/latest/html/users_guide/data-type-extensions.html#gadt-style

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


Re: [Haskell-cafe] Ambiguous reified dictionaries

2009-04-09 Thread Lennart Augustsson
That program is incorrect, it contains two instances for Monoid Int,
and the compiler should flag it as illegal.

   -- Lennart

On Thu, Apr 9, 2009 at 10:35 AM, Martijn van Steenbergen
 wrote:
> Good morning,
>
> The [1]GHC user's guide, section 8.4.5 says:
>
> "The new feature is that pattern-matching on MkSet (as in the definition of
> insert) makes available an (Eq a) context. In implementation terms, the
> MkSet constructor has a hidden field that stores the (Eq a) dictionary that
> is passed to MkSet; so when pattern-matching that dictionary becomes
> available for the right-hand side of the match."
>
> But what happens if there are several dictionaries available?
>
> Consider these three modules:
>
> ReifyMonoid.hs:
>
>> {-# LANGUAGE GADTs #-}
>>
>> module ReifyMonoid where
>>
>> import Data.Monoid
>>
>> data MonoidInst a where
>>  MkMonoidInst :: Monoid a => MonoidInst a
>
> ReifySum.hs:
>
>> module ReifySum where
>>
>> import ReifyMonoid
>> import Data.Monoid
>>
>> instance Monoid Int where
>>  mempty = 0
>>  mappend = (+)
>>
>> intSum :: MonoidInst Int
>> intSum = MkMonoidInst
>
> ReifyProd.hs:
>
>> module ReifyProd where
>>
>> import ReifyMonoid
>> import Data.Monoid
>>
>> instance Monoid Int where
>>  mempty = 1
>>  mappend = (*)
>>
>> intProd :: MonoidInst Int
>> intProd = MkMonoidInst
>
> Now a function
>
>> emp :: MonoidInst a -> a
>> emp MkMonoidInst = mempty
>
> works as you'd expect:
>
> *ReifySum ReifyProd> emp intSum
> 0
> *ReifySum ReifyProd> emp intProd
> 1
>
> But what about this function?
>
>> empAmb :: MonoidInst a -> MonoidInst a -> a
>> empAmb MkMonoidInst MkMonoidInst = mempty
>
> Now there are two dictionaries available. GHC consistently picks the one
> from the second argument:
>
> *ReifySum ReifyProd> empAmb intProd intSum
> 1
> *ReifySum ReifyProd> empAmb intSum intProd
> 0
>
> My questions are:
>
> 1) Shouldn't GHC reject this as being ambiguous?
> 2) Should class constraints only be available on existentially qualified
> type variables to prevent this from happening at all?
> 3) Is it possible to implement the following function?
>
>> mkMonoidInst :: a -> (a -> a -> a) -> MonoidInst a
>> mkMonoidInst mempty mappend = ...
>
> Thank you,
>
> Martijn.
>
>
>
> [1]
> http://www.haskell.org/ghc/docs/latest/html/users_guide/data-type-extensions.html#gadt-style
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] How to define a common return and bind?

2009-04-09 Thread Bas van Dijk
Hello,

Suppose you have defined a monad transformer such as:

> newtype T1 m a = T1 { unT1 :: A1 m a }

Where 'A1 m' is an arbitrary monad of your choosing.
For this discussion we just take the identity:

> type A1 m a = m a   -- (can be any monad)

If you want to define a Monad instance for 'T1 m' you generally do this:

instance Monad m => Monad (T1 m) where
return  = T1 . return
m >>= f = T1 $ unT1 m >>= unT1 . f

(I know I can use the 'GeneralizedNewtypeDeriving' language extension
to automatically derive a Monad but suppose that isn't available)

Now when I define a new monad transformer:

> newtype T2 m a = T2 { unT2 :: A2 m a }

Where 'A2 m' is again an arbitrary monad of your choosing but for now
just the identity:

> type A2 m a = m a   -- (can be any monad)

The Monad instance for it is almost completely identical to the former:

instance Monad m => Monad (T2 m) where
return  = T2 . return
m >>= f = T2 $ unT2 m >>= unT2 . f

Note that the only differences are:

 * a function to convert
   from the outer monad _to_ the inner monad:
   'unT1' and 'unT2'

 * a function to convert
   _from_ the inner monad to the outer monad:
   'T1' and 'T2'

The common parts seem to be:

liftReturn from = from . return
liftBind   from to m f = from $ to m >>= to . f

My question is: can these be given suitable and general enough types
so that they can be used to define Monad instances for monad
transformers?

In other words can I use them to write:

instance Monad m => Monad (T1 m) where
return = liftReturn T1
(>>=)  = liftBind   T1 unT1

and:

instance Monad m => Monad (T2 m) where
return = liftReturn T2
(>>=)  = liftBind   T2 unT2

Thanks,

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


[Haskell-cafe] WX: linking to system libraries statically

2009-04-09 Thread FFT
I noticed that even simple WX demos like "Layout" are linked
dynamically against 59 libraries on Linux. This would make
distributing the binaries a nightmare. Is there a simple way to make a
(mostly) statically linked binary?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Ambiguous reified dictionaries

2009-04-09 Thread Martijn van Steenbergen

Lennart Augustsson wrote:

That program is incorrect, it contains two instances for Monoid Int,
and the compiler should flag it as illegal.


Two simultaneous instances are okay as long as you don't use any of 
those instances, right? Just like two imported symbols with the same 
name are okay as long as you don't use them.


Martijn.

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


Re: [Haskell-cafe] Trying to write 'safeFromInteger'

2009-04-09 Thread Neil Mitchell
>>> That seems a really weird way to write it! Who decided all auxiliary
>>> functions should be called go? (I think I'm blaming dons) - why not:
>>>
>>> sffi :: (Integral a,Num a) => Integer -> Maybe a
>>> sffi n | toInteger n2 == n = Just n2
>>>        | otherwise = Nothing
>>>     where n2 = fromInteger n
>>
>> I know I was too lazy to clean it up :-P
>> ( I also blame Dons for 'go' )
>
> I think the Common Lisp community tends to use 'foo-aux' instead of
> 'go' for these sort of axillary functions.  But, then in Haskell we
> can't use hyphen as an identify character and underscore is not
> popular.  For this reason I started using fooAux in Haskell, but after
> learning that a single quote is valid identifier character I started
> using foo'.
>
> Other than using go and foo', what do people use in Haskell?

I use f, if I need several auxiliary functions I start at f and work
my way up alphabetically. I tend to go back to f2 if I go past h. Be
grateful you don't have to maintain my code :-)

Thanks

Neil

PS. Here is some code from the filepath library I wrote, illustrating
how fantastic my naming scheme looks. (I think if I was writing it
today I'd have used a list comprehension for validChars, eliminating
f.)

makeValid path = joinDrive drv $ validElements $ validChars pth
where
(drv,pth) = splitDrive path

validChars x = map f x
f x | x `elem` badCharacters = '_'
| otherwise = x

validElements x = joinPath $ map g $ splitPath x
g x = h (reverse b) ++ reverse a
where (a,b) = span isPathSeparator $ reverse x
h x = if map toUpper a `elem` badElements then a ++ "_" <.> b else x
where (a,b) = splitExtensions x
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Ambiguous reified dictionaries

2009-04-09 Thread Martijn van Steenbergen

Martijn van Steenbergen wrote:
Two simultaneous instances are okay as long as you don't use any of 
those instances, right? Just like two imported symbols with the same 
name are okay as long as you don't use them.


This makes little sense. Sorry, my bad. I was thinking about instances 
available in the complete module instead of also those made available by 
pattern matching on constructors.


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


RE: [Haskell-cafe] Ambiguous reified dictionaries

2009-04-09 Thread Simon Peyton-Jones
Yes, Haskell says that in any program there should be only one instance for any 
particular type (here Monoid Int).  GHC doesn't check that, but it should 
really do so.  It's not necessary for soundness (ie no runtime crash) but it is 
necessary for coherence (ie when you run the program the answer you get doesn't 
depend on which dictionary the typechecker arbitrarily chose).

[When type functions are involved, having a unique instance is necessary for 
soundness as well as coherence.]

This isn't the only place there may be a choice of dictionaries.  Consider

class Eq a => C a where ...
class Eq a => D a where ...

f :: (C a, D a) => a -> ...
f x = (x==x)

Here the type checker can get the Eq dictionary it needs for (x==x) from either 
the (C a) dictionary or the (D a) dictionary.


| > 3) Is it possible to implement the following function?
| >
| >> mkMonoidInst :: a -> (a -> a -> a) -> MonoidInst a
| >> mkMonoidInst mempty mappend = ...

No it's not possible.  And now you know why!

Simon


| -Original Message-
| From: haskell-cafe-boun...@haskell.org 
[mailto:haskell-cafe-boun...@haskell.org] On
| Behalf Of Lennart Augustsson
| Sent: 09 April 2009 09:54
| To: Martijn van Steenbergen
| Cc: Haskell Cafe
| Subject: Re: [Haskell-cafe] Ambiguous reified dictionaries
|
| That program is incorrect, it contains two instances for Monoid Int,
| and the compiler should flag it as illegal.
|
|-- Lennart
|
| On Thu, Apr 9, 2009 at 10:35 AM, Martijn van Steenbergen
|  wrote:
| > Good morning,
| >
| > The [1]GHC user's guide, section 8.4.5 says:
| >
| > "The new feature is that pattern-matching on MkSet (as in the definition of
| > insert) makes available an (Eq a) context. In implementation terms, the
| > MkSet constructor has a hidden field that stores the (Eq a) dictionary that
| > is passed to MkSet; so when pattern-matching that dictionary becomes
| > available for the right-hand side of the match."
| >
| > But what happens if there are several dictionaries available?
| >
| > Consider these three modules:
| >
| > ReifyMonoid.hs:
| >
| >> {-# LANGUAGE GADTs #-}
| >>
| >> module ReifyMonoid where
| >>
| >> import Data.Monoid
| >>
| >> data MonoidInst a where
| >>  MkMonoidInst :: Monoid a => MonoidInst a
| >
| > ReifySum.hs:
| >
| >> module ReifySum where
| >>
| >> import ReifyMonoid
| >> import Data.Monoid
| >>
| >> instance Monoid Int where
| >>  mempty = 0
| >>  mappend = (+)
| >>
| >> intSum :: MonoidInst Int
| >> intSum = MkMonoidInst
| >
| > ReifyProd.hs:
| >
| >> module ReifyProd where
| >>
| >> import ReifyMonoid
| >> import Data.Monoid
| >>
| >> instance Monoid Int where
| >>  mempty = 1
| >>  mappend = (*)
| >>
| >> intProd :: MonoidInst Int
| >> intProd = MkMonoidInst
| >
| > Now a function
| >
| >> emp :: MonoidInst a -> a
| >> emp MkMonoidInst = mempty
| >
| > works as you'd expect:
| >
| > *ReifySum ReifyProd> emp intSum
| > 0
| > *ReifySum ReifyProd> emp intProd
| > 1
| >
| > But what about this function?
| >
| >> empAmb :: MonoidInst a -> MonoidInst a -> a
| >> empAmb MkMonoidInst MkMonoidInst = mempty
| >
| > Now there are two dictionaries available. GHC consistently picks the one
| > from the second argument:
| >
| > *ReifySum ReifyProd> empAmb intProd intSum
| > 1
| > *ReifySum ReifyProd> empAmb intSum intProd
| > 0
| >
| > My questions are:
| >
| > 1) Shouldn't GHC reject this as being ambiguous?
| > 2) Should class constraints only be available on existentially qualified
| > type variables to prevent this from happening at all?
| > 3) Is it possible to implement the following function?
| >
| >> mkMonoidInst :: a -> (a -> a -> a) -> MonoidInst a
| >> mkMonoidInst mempty mappend = ...
| >
| > Thank you,
| >
| > Martijn.
| >
| >
| >
| > [1]
| > http://www.haskell.org/ghc/docs/latest/html/users_guide/data-type-
| extensions.html#gadt-style
| > ___
| > Haskell-Cafe mailing list
| > Haskell-Cafe@haskell.org
| > http://www.haskell.org/mailman/listinfo/haskell-cafe
| >
| ___
| Haskell-Cafe mailing list
| Haskell-Cafe@haskell.org
| http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Monads from Functors

2009-04-09 Thread Sebastian Fischer

Hi all,

thanks for pointing me at the Codensity monad and for mentioning the
lift operation! I'll try to sum up what I learned from this thread.

In short:

What I find interesting is

  1. you can express the results of monadic computations using
 functors that do not themselves support the `>>=` operation. You
 only need an equivalent of `return`.

and

  2. a variety of *non-*monadic effects (e.g., non-determinism) can be
 lifted to this "monad for free", so you get, e.g., a
 non-determinism *monad* even if all you have is a non-determinism
 *functor*.

Here is the long version:

Because `ContT` makes a monad out of anything with kind `* -> *`, we
also get instances for `Functor` and `Applicative` for free. We could
use the `Monad` instance to get them for free by
`Control.Applicative.WrappedMonad` but defining them from scratch
might be insightful, so let's try.

We could define an instance of `Functor` for `ContT t` as follows.

instance Functor (ContT t)
 where
  fmap = liftM

But let's see what we get if we inline this definition:

fmap f a
  = liftM f a
  = a >>= return . f
  = ContT (\k -> unContT a (\x -> unContT (return (f x)) k))
  = ContT (\k -> unContT a (\x -> unContT (ContT ($f x)) k))
  = ContT (\k -> unContT a (\x -> k (f x)))

That leads to the `Functor` instance described in the first post on
Kan extensions by Edward Kmett.

> instance Functor (ContT t)
>  where
>   fmap f a = ContT (\k -> unContT a (k.f))

We also get an Applicative instance for free:

instance Applicative (ContT t)
 where
  pure  = return
  (<*>) = ap

If we inline `ap` we get

f <*> a
  = f `ap` a
  = f >>= \g -> a >>= \x -> return (g x)
  = ContT (\k1 -> unContT f (\x1 -> unContT (a >>= \x -> return (x1  
x)) k1))

  = ...
  = ContT (\k -> unContT f (\g -> unContT a (\x -> k (g x

So, a direct Applicative` instance would be:

> instance Applicative (ContT t)
>  where
>   pure x  = ContT ($x)
>   f <*> a = ContT (\k -> unContT f (\g -> unContT a (\x -> k (g x

The more interesting bits are conversions between the original and the
lifted types. As mentioned earlier, if `f` is a pointed functor, then
we can convert values of type `ContT f a` to values of type `f a`.

runContT :: Pointed f => ContT f a -> f a
runContT a = unContT a point

Ryan Ingram pointed in the other direction:

 > You are missing one important piece of the puzzle for ContT:
 >
 > ~~~
 > lift :: Monad m => m a -> ContT m a
 > lift m = ContT $ \k -> m >>= k
 > ~~~
 >
 > This >>= is the bind from the underlying monad.  Without this
 > operation, it's not very useful as a transformer!

That is a fine reason for the *class* declaration of `MonadTrans` to
mention `Monad m` as a constraint for `lift`. But as `ContT t` is a
monad for any `t :: * -> *`, a constraint `Monad t` on the *instance*
declaration for `Monad (ContT t)` is moot. This constraint is not
necessary to define `lift`.

> instance MonadTrans ContT
>  where
>   lift m = ContT (m>>=)

Ryan continues:

 > Without lift, it's quite difficult to get effects from the
 > underlying Applicative *into* ContT.  Similarily, your MonadPlus
 > instance would be just as good replacing with the "free"
 > alternative functor:
 >
 > ~~~
 > data MPlus a = Zero | Pure a | Plus (MPlus a) (MPlus a)
 > ~~~
 >
 > and then transforming MPlus into the desired type after runContT;
 > it's the embedding of effects via lift that makes ContT useful.

Let's see whether I got your point here. If we have a computation

a :: Monad m => m a

and we have a pointed functor `f`, then we can get the result of the
computation `a` in our functor `f` because `runContT a :: f a`.

If we now have a computation with additional monadic effects (I use
non-determinism as a specific effect, but Edward Kmett shows in his
second post on Kan extensions how to lift other effects like Reader,
State, and IO)

b :: MonadPlus m => m b

then we have two possibilities to express the result using `f` if `f` is
also an alternative functor.

  1. If `f` is itself a monad (i.e. an instance of MonadPlus), then
 the expression `runContT (lift b)` has type `f b`. (Well, `b`
 itself has type `f b`..)

  2. If `f` is *not* a monad, we can still get the result of `b` in
 our functor `f` (using the `MonadPlus` instance from my previous
 mail), because `runContT b` also has type `f b`.

Clearly, `runContT (lift b)` (or `b` itself) and `runContT b` may
behave differently (even if they both (can) have the type `f b`)
because `ContT` 'overwrites' the definition for `>>=` of `f` if `f`
has one. So it depends on the application which of those behaviours is
desired.

Ryan:

 > The CPS transfrom in ContT also has the nice property that it makes
 > most applications of >>= in the underlying monad be
 > right-associative.

Do you have a specific reason to say *most* (rather than *all*) here?
Because if we have a left-associative application of `>>=` in `ContT`,
then we hav

[Haskell-cafe] Debugging compile times (Template Haskell)

2009-04-09 Thread Henning Günther
Hi,

as the author of the encoding package[1] I'm quite annoyed by the
extreeme long time it takes to compile a certain module (JISX0208). This
module uses template haskell to generate both a Map (Map Char
(Word8,Word8)) and an Array (UArray (Word8,Word8) Int) for character
conversion. The file has about 6000 entries and the generated array has
8649 entries. Generating the syntax for the array and map is very fast
(under a second) but compiling the code seems to take forever.
Is there any way to find out why that is the case? I've tried
pinpointing the problem but couldn't...

[1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/encoding


signature.asc
Description: Dies ist ein digital signierter Nachrichtenteil
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ghci *.hs

2009-04-09 Thread Paul Keir
Hi all,

I like to use ghci *.hs to start my session, but I then have to type :m +Main
to bring the Main module into scope. Is there a command-line switch to control
which modules are initially in scope with ghci?

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


Re: [Haskell-cafe] Debugging compile times (Template Haskell)

2009-04-09 Thread Bulat Ziganshin
Hello Henning,

Thursday, April 9, 2009, 5:01:21 PM, you wrote:

i think that this case may be interesting for GHC developers

> Hi,

> as the author of the encoding package[1] I'm quite annoyed by the
> extreeme long time it takes to compile a certain module (JISX0208). This
> module uses template haskell to generate both a Map (Map Char
> (Word8,Word8)) and an Array (UArray (Word8,Word8) Int) for character
> conversion. The file has about 6000 entries and the generated array has
> 8649 entries. Generating the syntax for the array and map is very fast
> (under a second) but compiling the code seems to take forever.
> Is there any way to find out why that is the case? I've tried
> pinpointing the problem but couldn't...

> [1]
> http://hackage.haskell.org/cgi-bin/hackage-scripts/package/encoding



-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


[Haskell-cafe] GHC: compile using multiple cores?

2009-04-09 Thread Peter Verswyvelen
Is it possible to use all CPU cores when compiling with GHC and/or Cabal?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Problems getting errors with HXT

2009-04-09 Thread rodrigo.bonifacio
Hi all,
I'm trying to get valitation errors with HXT / RelaxNG schemas. For instance, an error is reported when I  run the following code. However, the return of getErrors is an empty list.
> main :: IO ()> main = do >   rc <- runX ( readDocument [] "input.xml">    >>> >     validateDocumentWithRelaxSchema [] "schema.rng">     >>> >    getErrors> )>   print rc
How can I get the list of errors?
Thanks in advance,
Rodrigo.
 
 
 
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: GHC: compile using multiple cores?

2009-04-09 Thread Achim Schneider
Peter Verswyvelen  wrote:

> Is it possible to use all CPU cores when compiling with GHC and/or
> Cabal?
> 
Nope. Last thing I heard is that file-parallel compilation is low
priority as not much would be gained anyway due to excessive
cross-package stuff that's done and much stricter dependencies than say
C (which you can compile in about any order you like). I guess if such
a thing happens, it'd be most likely in the form of strategically
placed `par`'s inside of compiler stages.

-- 
(c) this sig last receiving data processing entity. Inspect headers
for copyright history. All rights reserved. Copying, hiring, renting,
performance and/or quoting of this signature prohibited.


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


Re: [Haskell-cafe] Trying to write 'safeFromInteger'

2009-04-09 Thread Ketil Malde
Neil Mitchell  writes:

>> Other than using go and foo', what do people use in Haskell?

I tend to use 'go' for recursive or iterative functions.  Which I
belive is the original dons idiom.

I occasionally use foo', but it is all too easy to write foo when you
mean foo', and, which is worse, it occasionally happens to compile.

> I use f, if I need several auxiliary functions I start at f and work
> my way up alphabetically.

:-)

> makeValid path = joinDrive drv $ validElements $ validChars pth
> where
> (drv,pth) = splitDrive path
>
> validChars x = map f x
> f x | x `elem` badCharacters = '_'
> | otherwise = x

In cases like this, I use names like 'foo1', since it does 'foo' for
one element.  So here I'd name 'f' something like 'valid1'.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: GHC: compile using multiple cores?

2009-04-09 Thread Don Stewart
barsoap:
> Peter Verswyvelen  wrote:
> 
> > Is it possible to use all CPU cores when compiling with GHC and/or
> > Cabal?
> > 
> Nope. Last thing I heard is that file-parallel compilation is low
> priority as not much would be gained anyway due to excessive
> cross-package stuff that's done and much stricter dependencies than say
> C (which you can compile in about any order you like). I guess if such
> a thing happens, it'd be most likely in the form of strategically
> placed `par`'s inside of compiler stages.
> 

Not with cabal, with GHC, yes: assuming you have enough modules. Use ghc
-M to dump a makefile, and then make -j20 (or whatever you have)

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


[Haskell-cafe] Referential Transparency and Monads

2009-04-09 Thread Mark Spezzano
Hi,

 

How exactly do monads “solve” the problem of referential transparency? I
understand RT to be such that a function can be replaced with a actual
value. 

 

Since a monad could potentially encapsulate any other value—say, data read
from a keyboard—doesn’t that violate the assumption of RT on monads?

 

Or does RT ignore the encapsulated data and just view the “action” performed
by the monad as the “value” of the monad?

 

Just curious as to the rationale behind referential transparency and how it
applies to monads.

 

Cheers,

 

Mark Spezzano

 


No virus found in this outgoing message.
Checked by AVG. 
Version: 7.5.557 / Virus Database: 270.11.48/2048 - Release Date: 8/04/2009
7:02 PM
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: GHC: compile using multiple cores?

2009-04-09 Thread Neil Mitchell
> Not with cabal, with GHC, yes: assuming you have enough modules. Use ghc
> -M to dump a makefile, and then make -j20 (or whatever you have)

There is a performance penalty to running ghc on separate files vs
--make. If your number of core's is limited --make may be better. I'd
love someone to figure out what the cross over point is :-)

As a related question, how does GHC implement -j3? For my programs, if
I want to run in parallel, I have to type +RTS -N3. Can I use the same
trick as GHC?

Thanks

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


RE: [Haskell-cafe] Strange type error with associated type synonyms

2009-04-09 Thread Simon Peyton-Jones

| | -- f' :: forall d a. (Fun d) => Memo d a -> Memo d a
| | f' = abst . (id :: (d->a)->(d->a)) . appl
| |
| | There is a perfectly valid type signature for f', as given in
| | comment, but GHCi gives an incorrect one (the same as for f):
| |
| | *Main> :browse Main
| | class Fun d where
| |   abst :: (d -> a) -> Memo d a
| |   appl :: Memo d a -> d -> a
| | f :: (Fun d) => Memo d a -> Memo d a
| | f' :: (Fun d) => Memo d a -> Memo d a
|
| >I'm missing something here.  Those types are identical to the one given
| >in your type signature for f' above, save that the forall is suppressed
| >(because you are allowed to omit it, and GHC generally does when
| >printing types).
|
| Not with ScopedTypeVariables, though, where explicit foralls have
| been given an additional significance. Uncommenting the f' signature works, 
while
| dropping the
| 'forall d a' from it fails with
| the usual match failure due to ambiguity "Couldn't match expected
| type `Memo d1' against inferred type `Memo d'".

Oh now i see what you mean:  consider
f' = abst . (id :: (d->a)->(d->a)) . appl
which GHC understands to mean
f' = abst . (id :: forall d a. (d->a)->(d->a)) . appl

GHC infers the type
f' :: (Fun d) => Memo d a -> Memo d a
Now you are saying that GHC *could* have figured out that if it added the 
signature
f' :: forall d a. (Fun d) => Memo d a -> Memo d a
thereby *changing* the scoping of d,a in the buried signature for 'id', doing 
so would not change whether f' was typeable or not.  Well maybe, but that is 
way beyond what I have any current plans to do.

S

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


Re: [Haskell-cafe] Referential Transparency and Monads

2009-04-09 Thread Paul Keir
I think this topic is covered in Andrew Gordon's dissertation/book:
Functional programming and input/output by Andrew D. Gordon
You can read it online.
Cheers,
Paul
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Referential Transparency and Monads

2009-04-09 Thread Brandon S. Allbery KF8NH

On 2009 Apr 9, at 11:47, Mark Spezzano wrote:
How exactly do monads “solve” the problem of referential  
transparency? I understand RT to be such that a function can be  
replaced with a actual value.


Since a monad could potentially encapsulate any other value—say,  
data read from a keyboard—doesn’t that violate the assumption of RT  
on monads?


Monads provide a way to carry extra data or operations around with  
their values.  IO passes an opaque "world state" around in the  
background, conceptually I/O operations modify the "world state" and  
it is in fact always valid to replace the monadified version with the  
unwrapped version --- ignoring IORefs, IO is just a simple state monad.


The "world state" insures that operations in the IO monad are  
constrained to an ordered list.  This gives us a referentially  
transparent *model* that behaves the way we need it to; the fact that  
actual I/O is not referentially transparent doesn't matter because the  
model insures that computations in IO behave properly.  (Unless you  
use unsafePerformIO or unsafeInterleaveIO, which is why they're  
unsafe; you've violated the model, unexpected things can happen as a  
result.)


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




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


Re: [Haskell-cafe] Monads from Functors

2009-04-09 Thread Ryan Ingram
On Thu, Apr 9, 2009 at 2:22 AM, Sebastian Fischer
 wrote:
> Let's see whether I got your point here. If we have a computation
>
>    a :: Monad m => m a
>
> and we have a pointed functor `f`, then we can get the result of the
> computation `a` in our functor `f` because `runContT a :: f a`.

Sure, but you can also do the same much more simply:

mkPointed :: Pointed f => forall f a. (forall m. Monad m => m a) -> f a
mkPointed m = point $ runIdentity m

> Clearly, `runContT (lift b)` (or `b` itself) and `runContT b` may
> behave differently (even if they both (can) have the type `f b`)
> because `ContT` 'overwrites' the definition for `>>=` of `f` if `f`
> has one. So it depends on the application which of those behaviours is
> desired.

My point was slightly more general; what I was saying was there is not
a huge use for the "generic" MonadPlus using Alternative, because
without "lift", you have a hard time embedding any other effects from
the applicative into the continuation use.  You may as well do the
following:

> data MPlus a = Zero | Pure a | Plus (MPlus a) (MPlus a)
> instance Monad MPlus where
>return = Pure
>Zero >>= k = Zero
>Pure a >>= k = k a
>Plus a b >>= k = Plus (a >>= k) (b >>= k)
> instance MonadPlus MPlus where
>mzero = Zero
>mplus = Plus

> mkAlternative :: forall f a. Alternative f => (forall m. MonadPlus m => m a) 
> -> f a
> mkAlternative m = convertPlus m where
>convertPlus :: forall b. MPlus b -> f b
>convertPlus Zero = empty
>convertPlus (Pure a) = pure a
>convertPlus (Plus a b) = convertPlus a <|> convertPlus b

(all this code is really saying is that being polymorphic over
MonadPlus is kind of dumb, because you aren't really using Monad at
all)

Without any way to lift other effects from the underlying functor into
ContT, I don't really see how the "generic" ContT MonadPlus instance
buys you much :)

> Ryan:
>  > The CPS transfrom in ContT also has the nice property that it makes
>  > most applications of >>= in the underlying monad be
>  > right-associative.
>
> Do you have a specific reason to say *most* (rather than *all*) here?

Yes, because
>  runContT ( (lift (a >>= f)) >>= g )
still has a left-associative >>=.

Now of course that looks silly, but things aren't as simple as they
seem; in particular I ran into this first when using
Control.Monad.Prompt[1] (which is really just a sophisticated Cont
monad with a nice interface)

> data MPlus m a = Zero | Plus (m a) (m a)
>
> instance MonadPlus (RecPrompt MPlus) where
> mzero = prompt Zero
> mplus x y = prompt (Plus x y)
>
> runPlus :: forall a. RecPrompt MPlus r -> [r]
> runPlus = runPromptC ret prm . unRecPrompt where
>ret :: r -> [r]
>ret x = [x]
>
>prm :: forall a. MPlus (RecPrompt MPlus) a -> (a -> [r]) -> [r]
>prm Zero k = []
>prm (Plus a b) k = (runPlus a ++ runPlus b) >>= k
>-- this >>= is in the list monad

Now, consider runPlus ((mplus mzero (a >>= f)) >>= g), which uses the
Plus "effect"; this will reduce to
(runPlus (a >>= f)) >>= k
where k is the continuation that runs g using "ret" and "prm" to
convert to a list; the result still may have a left-associated >>= in
it, depending on the value of "a" and "f".

However, you're limited to at most one left associative bind per
"recursive" lifted operation; the other binds will all be
right-associative.

I know this was a pretty in-depth example, so I hope I've made it clear :)

  -- ryan

[1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/MonadPrompt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monads from Functors

2009-04-09 Thread Edward Kmett
I think there is another way to view the ContT/Codensity/Monad generated by
a functor, in terms of an accumulating parameter that may be informative. I
kind of alluded to it in the post on Kan extensions.

Take for a moment, Yoneda f given in:

http://comonad.com/haskell/category-extras/src/Control/Functor/Yoneda.hs

> newtype Yoneda f a = Yoneda { runYoneda :: forall b. (a -> b) -> f b }

You can readily construct an instance of Functor for Yoneda without any
concern for the underlying instance on f.

> instance Functor (Yoneda f) where
> fmap f m = Yoneda (\k -> runYoneda m (k . f))

> lowerYoneda :: Yoneda f a -> f a
> lowerYoneda m = runYoneda m id

Basically the operation of creating a value of type Yoneda f a requires you
to use the fmap for the functor, so there is a Mendler-style encoding going
on here, no magic dictionaries are required to use the resulting value.
Now what I find interesting is that Yoneda is basically carrying around an
accumulator for 'fmap' applications.

Basically it enforces the fusion rule that fmap f . fmap g = fmap (f . g) by
accumulating mappings and applying them in one go when you ask for the
result.

As an aside, when you extract a value out of (Yoneda f) uses the function it
has accumulated so far, from pushing computations. And it has to use the
secret valid version of fmap that you had to know to find a function that
had the signature (forall a. (a -> b) -> f b) so no work is saved, its just
fmap fusion.

When you make a Monad out of Yoneda, that Monad can 'push' the map along to
the next bind operation so it can come along for the ride, avoiding the need
for an extra (>>=) to liftM the function you want to map. (It still has to
appeal to the secret fmap you knew to make the Yoneda f a value!) Of course,
this steps outside of the principles I'm espousing in this post by using a
dictionary.

> instance Monad f => Monad (Yoneda f) where
>   return a = Yoneda (\f -> return (f a))
>   m >>= k = Yoneda (\f -> runYoneda m id >>= \a -> runYoneda (k a) f)

When you look at the definition for Codensity f a, what it effectively
supplies is a 'better accumulator', one which is large enough to encode
(>>=).

> newtype Codensity m a = Codensity { runCodensity :: forall b. (a -> m b)
-> m b }

> instance Monad (Codensity f) where
>   return x = Codensity (\k -> k x)
>   m >>= k = Codensity (\c -> runCodensity m (\a -> runCodensity (k a) c))

You then have to pass it a function of the type (a -> m b) to get the value
out. Effectively you tell it how to return by injecting something. And since
it can return and bind, you can define liftM thanks to the monad laws,
giving an admissable implementation of Functor:

 > instance Functor (Codensity k) where
>   fmap f m = Codensity (\k -> runCodensity m (k . f))

Again no dictionaries were harmed in the encoding of this function and the
type is no bigger than it needs to be to express these properties.

The Codensity monad above can be seen as just an instance of enforced bind
fusion, enforcing choice of association of (>>=). This consequence
is logical because the result of a CPS transform is invariant under choice
of reduction order.

The reason I mention this is that this scenario is just an instance of
a very general pattern of Mendler-style encoding. I have another example of
Mendler-style encoding, this time for recursion schemes near the bottom of:
http://knol.google.com/k/edward-kmett/catamorphisms/

I find this idiom to be rather effective when I want to enforce the
equivalent of a rewrite rule or law about a type or work around the
requirement that there can be only one instance of a particular typeclass.
Yoneda doesn't care that f implements Functor, only that it satisfies the
properties of a functor, and that fmap _could_ be defined for it. Codensity
doesn't care that f is a monad. Well, it does if you want to do any
computations with f, but you could have several different lifts to different
monad/applicative 'instances' over f, as long as you lift into the codensity
monad with a bind operation and lower back out with a return operation that
agree. The dictionary for Monad m is irrelevant to the construction of
Codensity m.

> liftCodensity :: Monad m => m a ->  Codensity m a
> liftCodensity m = Codensity (m >>=)

> lowerCodensity :: Monad m => Codensity m a -> m a
> lowerCodensity a = runCodensity a return

-Edward Kmett


On Thu, Apr 9, 2009 at 5:22 AM, Sebastian Fischer <
s...@informatik.uni-kiel.de> wrote:

> Hi all,
>
> thanks for pointing me at the Codensity monad and for mentioning the
> lift operation! I'll try to sum up what I learned from this thread.
>
> In short:
>
> What I find interesting is
>
>  1. you can express the results of monadic computations using
> functors that do not themselves support the `>>=` operation. You
> only need an equivalent of `return`.
>
> and
>
>  2. a variety of *non-*monadic effects (e.g., non-determinism) can be
> lifted to this "monad for free", so you get, e.g., a
>

Re: [Haskell-cafe] Referential Transparency and Monads

2009-04-09 Thread Luke Palmer
2009/4/9 Mark Spezzano 

> Or does RT ignore the encapsulated data and just view the “action”
> performed by the monad as the “value” of the monad?
>

If I understand you right, this is more-or-less correct.

You may as well think of IO as some sort of algebraic type that you are
building and returning.  A value of type "IO Integer" is not, itself, an
integer.  Thus:

main =
  let r = print "hello"
  in return ()

Prints nothing.  RT steps in in a similar scenario:

main =
  let r = print "hello"
  in do { r; r }

Replacing "r" with its definition:

main = do { print "hello"; print "hello" }

As expected.

Luke



>
> Just curious as to the rationale behind referential transparency and how it
> applies to monads.
>
>
>
> Cheers,
>
>
>
> Mark Spezzano
>
>
>
> No virus found in this outgoing message.
> Checked by AVG.
> Version: 7.5.557 / Virus Database: 270.11.48/2048 - Release Date: 8/04/2009
> 7:02 PM
>
> ___
> 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] Referential Transparency and Monads

2009-04-09 Thread Jonathan Cast
On Thu, 2009-04-09 at 12:31 -0400, Brandon S. Allbery KF8NH wrote:
> On 2009 Apr 9, at 11:47, Mark Spezzano wrote:
> > How exactly do monads “solve” the problem of referential
> > transparency? I understand RT to be such that a function can be
> > replaced with a actual value.
> >  
> > Since a monad could potentially encapsulate any other value—say,
> > data read from a keyboard—doesn’t that violate the assumption of RT
> > on monads?

> Monads provide a way to carry extra data or operations around with
> their values.  IO passes an opaque "world state" around in the
> background, conceptually I/O operations modify the "world state" and
> it is in fact always valid to replace the monadified version with the
> unwrapped version --- ignoring IORefs, IO is just a simple state
> monad.

I'm not sure what you mean by that, but semantically IO is definitely
*not* a state monad.  Under any circumstances or any set of assumptions.

GHC *implements* IO as a state monad, but not because it semantically
is.  Rather, GHC's back-end language (STG) is an *impure* lazy
functional language, supplying primitive functions with (ultimate)
result type

(# State# s, alpha #)

, for some alpha,[1] that are side-effectful.  The intention is that the
State# s component (which has almost no run-time representation) is used
to ensure a strict sequencing of the evaluation of these expressions ---
which intention can be violated by using the operations unsafePerformIO
and unsafeInterleaveIO --- allowing the language to be both
side-effectful and lazy without the programmer necessarily effectively
losing the ability to control what the outcome of running the program
will be.

But that has nothing to do with referential transparency, because the
language those tricks are used in is not referentially transparent.
It's just an implementation technique for implementing a referentially
transparent source language on a non-referentially transparent
imperative stored-memory computer.

jcc

[1] As pointed out in another thread a couple of weeks ago, the order of
these components is reversed: they should be

(# alpha, State# s #)

It's probably too late to change it now, though.


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


[Haskell-cafe] Re: WX: linking to system libraries statically

2009-04-09 Thread Eric Kow
Hi FFT,

I'm just CC'ing wxhaskell-users so they see this question.

Thanks!

On Thu, 9 Apr 2009 04:13:18 -0700, FFT wrote
> I noticed that even simple WX demos like "Layout" are linked
> dynamically against 59 libraries on Linux. This would make
> distributing the binaries a nightmare. Is there a simple way to make a
> (mostly) statically linked binary?

-- 
Eric Kow 
PGP Key ID: 08AC04F9


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


Re: [Haskell-cafe] Referential Transparency and Monads

2009-04-09 Thread Miguel Mitrofanov

I'm not sure what you mean by that, but semantically IO is definitely
*not* a state monad.  Under any circumstances or any set of  
assumptions.


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


[Haskell-cafe] Re: Paper: Translating donotation to SQL, Leijden, Meijer

2009-04-09 Thread Chung-chieh Shan
Gü?nther Schmidt  wrote in article 
 in gmane.comp.lang.haskell.cafe:
> is the paper "Translating donotation to SQL, Leijden, Meijer (1999)" 
> available anywhere?

Seems to be here
http://www.usenix.org/events/dsl99/full_papers/leijen/leijen_html/
no?

-- 
Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig
100 Days to close Guantanamo and end torture http://100dayscampaign.org/

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


Re: [Haskell-cafe] Referential Transparency and Monads

2009-04-09 Thread Luke Palmer
On Thu, Apr 9, 2009 at 1:33 PM, Miguel Mitrofanov wrote:

> I'm not sure what you mean by that, but semantically IO is definitely
>> *not* a state monad.  Under any circumstances or any set of assumptions.
>>
>
> Ehm? Why not?


Mainly forkIO.  There may be other reasons.

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


Re: [Haskell-cafe] ghci *.hs

2009-04-09 Thread Henk-Jan van Tuyl

On Thu, 09 Apr 2009 15:44:42 +0200, Paul Keir  wrote:


Hi all,

I like to use ghci *.hs to start my session, but I then have to type :m  
+Main
to bring the Main module into scope. Is there a command-line switch to  
control

which modules are initially in scope with ghci?

Thanks,
Paul


You only have load the main module like this:
  ghci Main.lhs

(the name doesn't have to be Main.lhs or Main.hs), the rest follows  
automatically, provided the imported modules start with a line like:



module ImportModule2 where


It is also possible to run the program immediately with the command:
  runhaskell Main.lhs

--
Regards,
Henk-Jan van Tuyl


--
http://functor.bamikanarie.com
http://Van.Tuyl.eu/
--


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


Re: [Haskell-cafe] Strange type error with associated type synonyms

2009-04-09 Thread Claus Reinke

|Oh now i see what you mean:  consider
|f' = abst . (id :: (d->a)->(d->a)) . appl
|which GHC understands to mean
|f' = abst . (id :: forall d a. (d->a)->(d->a)) . appl
|
|GHC infers the type
|f' :: (Fun d) => Memo d a -> Memo d a
|Now you are saying that GHC *could* have figured out that if it added the 
signature
|f' :: forall d a. (Fun d) => Memo d a -> Memo d a
|thereby *changing* the scoping of d,a in the buried signature for 'id', doing so would not change 
whether f' was |typeable or not.  Well maybe, but that is way beyond what I have any current plans 
to do.


Indeed!-) I didn't mean to suggest this as a course of action, it was
just a way of representing the internal type inference intermediates
at source level. Another aspect I would not like about this approach is
that renamings of bound type variables would no longer be meaning-
preserving (because the signature would be interpreted in the context
of the source-code it belongs to) - not good.

But the core part of my suggestion (which this example was meant
to help explain) remains attractive, at least to me: somewhere during
type inference, GHC *does* unify the *apparently free* 'd' with an
internal type variable (lets call it 'd1, as in the type error message)
that has no explicit counterpart in source code or type signature,
so the inferred type should not be

   f' :: forall d. (Fun d) => Memo d a -> Memo d a -- (1)

but rather

   f' :: forall d. (Fun d,d~d1) => Memo d a -> Memo d a -- (2)

That way, the internal dependency would be made explicit in
the printed representation of the inferred type signature, and
the unknown 'd1' would appear explicitly in the inferred type,
not just in the error message (the explicit foralls are needed
here to make it clear that 'd1' and by implication, 'd', *cannot*
be freely generalized - 'd' is qualified by the equation with the
unknown 'd1').

To me, (2) makes more sense as an inferred type for f' than (1),
especially as it represents an obviously unusable type signature
(we don't know what 'd1' is, and we can't just unify it with anything),
whereas (1) suggests a useable type signature, but one that will fail
when used:

   Couldn't match expected type `Memo d1' against inferred
   type `Memo d'.

All I'm suggesting is that the type *printed* by GHCi does not
really represent the type *inferred* by GHCi (or else there should
not be any attempt to match the *free* 'd' against some unknown
'd1', as the error message says), and that there might be ways to 
make the discrepancy explicit, by printing the inferred type differently.


Claus


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


Re: [Haskell-cafe] Ambiguous reified dictionaries

2009-04-09 Thread Edward Kmett
On Thu, Apr 9, 2009 at 5:14 AM, Simon Peyton-Jones 
 wrote:

> | > 3) Is it possible to implement the following function?
> | >
> | >> mkMonoidInst :: a -> (a -> a -> a) -> MonoidInst a
> | >> mkMonoidInst mempty mappend = ...
>
> No it's not possible.  And now you know why!
>
> Simon
>

Simon,

While we can't give him exactly what he asked for, we can approximate the
construction using Oleg and CC Shan's Implicit Configurations and fulfill
the spirit of the request.
> {-# LANGUAGE ScopedTypeVariables, TypeOperators, MultiParamTypeClasses,
FlexibleContexts, UndecidableInstances, Rank2Types,
GeneralizedNewtypeDeriving #-}

Please, pardon the gratuitous use of extensions.

> import Data.Bits
> import Data.Monoid
> import Data.Reflection -- from package 'reflection'

First define the concept of a dictionary for a monoid.

>  type M a = (a, a -> a -> a)

Then provide a type level brand that indicates which dictionary you are
going to use.

> data (a `WithMonoid` s) = Mon { getWithMonoid :: a } deriving
(Eq,Ord,Show)

Use reflection to access the dictionary

> instance (s `Reflects` M a) => Monoid (a `WithMonoid` s) where
> mempty = Mon (fst (reflect (undefined :: s)))
> Mon a `mappend` Mon b = Mon ((snd (reflect (undefined :: s))) a b)

Reify a monoid dictionary for use within a universally quantified world, ala
ST.

> reifyMonoid :: a -> (a -> a -> a) -> (forall s. (s `Reflects` M a) => s ->
w) -> w
> reifyMonoid = curry reify

Change the type of the above to avoid the spurious argument, and to
automatically unwrap the result.

> withMonoid :: a -> (a -> a -> a) -> (forall s. (s `Reflects` M a) => w
`WithMonoid` s) -> w
> withMonoid = withMonoid' undefined where
>withMonoid' :: w -> a -> (a -> a -> a) -> (forall s. (s `Reflects` M a)
=> w `WithMonoid` s) -> w
>withMonoid' (_::w) (i::a) f k = reifyMonoid i f (\(_::t) ->
getWithMonoid (k :: w `WithMonoid` t))

And now we have some likely candidates to test:

> test :: Int
> test = withMonoid 0 (+) (mconcat [Mon 2,mempty,Mon 0])

> test2 :: Int
> test2 = withMonoid 1 (*) (mconcat [Mon 3,mempty,Mon 2])

> test3 :: Integer
> test3 = withMonoid 0 xor (mconcat [Mon 4,mempty,Mon 4])

*Main> test
Loading package reflection-0.1.1 ... linking ... done.
2
*Main> test2
6
*Main> test3
0

There you have it, everything works out.

Amusingly, I have a similar set of constructions for reifying other kinds of
constructs in my 'monoids' library on Hackage, but I don't currently provide
a reified Monoid type, mainly because the signature isn't enough to enforce
its associativity.

However, I do allow you to reify an arbitrary function into a 'Reducer'
using this trick to enable you to uniformly inject values into a particular
monoid.

-Edward Kmett


> | -Original Message-
> | From: haskell-cafe-boun...@haskell.org [mailto:
> haskell-cafe-boun...@haskell.org] On
> | Behalf Of Lennart Augustsson
> | Sent: 09 April 2009 09:54
> | To: Martijn van Steenbergen
> | Cc: Haskell Cafe
> | Subject: Re: [Haskell-cafe] Ambiguous reified dictionaries
> |
> | That program is incorrect, it contains two instances for Monoid Int,
> | and the compiler should flag it as illegal.
> |
> |-- Lennart
> |
> | On Thu, Apr 9, 2009 at 10:35 AM, Martijn van Steenbergen
> |  wrote:
> | > Good morning,
> | >
> | > The [1]GHC user's guide, section 8.4.5 says:
> | >
> | > "The new feature is that pattern-matching on MkSet (as in the
> definition of
> | > insert) makes available an (Eq a) context. In implementation terms, the
> | > MkSet constructor has a hidden field that stores the (Eq a) dictionary
> that
> | > is passed to MkSet; so when pattern-matching that dictionary becomes
> | > available for the right-hand side of the match."
> | >
> | > But what happens if there are several dictionaries available?
> | >
> | > Consider these three modules:
> | >
> | > ReifyMonoid.hs:
> | >
> | >> {-# LANGUAGE GADTs #-}
> | >>
> | >> module ReifyMonoid where
> | >>
> | >> import Data.Monoid
> | >>
> | >> data MonoidInst a where
> | >>  MkMonoidInst :: Monoid a => MonoidInst a
> | >
> | > ReifySum.hs:
> | >
> | >> module ReifySum where
> | >>
> | >> import ReifyMonoid
> | >> import Data.Monoid
> | >>
> | >> instance Monoid Int where
> | >>  mempty = 0
> | >>  mappend = (+)
> | >>
> | >> intSum :: MonoidInst Int
> | >> intSum = MkMonoidInst
> | >
> | > ReifyProd.hs:
> | >
> | >> module ReifyProd where
> | >>
> | >> import ReifyMonoid
> | >> import Data.Monoid
> | >>
> | >> instance Monoid Int where
> | >>  mempty = 1
> | >>  mappend = (*)
> | >>
> | >> intProd :: MonoidInst Int
> | >> intProd = MkMonoidInst
> | >
> | > Now a function
> | >
> | >> emp :: MonoidInst a -> a
> | >> emp MkMonoidInst = mempty
> | >
> | > works as you'd expect:
> | >
> | > *ReifySum ReifyProd> emp intSum
> | > 0
> | > *ReifySum ReifyProd> emp intProd
> | > 1
> | >
> | > But what about this function?
> | >
> | >> empAmb :: MonoidInst a -> MonoidInst a -> a
> | >> empAmb MkMonoidInst MkMonoidInst = mempty
> | >
> | > No

Re: [Haskell-cafe] ANN: network-bytestring 0.1.2

2009-04-09 Thread Thomas DuBuisson
Johan,
This doesn't build for me on ghc-6.10.2.  It looks like an internal
part of the network library changed, but I didn't give it much
thought.

Thomas


[...@mavlo network-data]$ cabal install network-bytestring
Resolving dependencies...
[1 of 1] Compiling Main (
/tmp/network-bytestring-0.1.214361/network-bytestring-0.1.2/Setup.hs,
/tmp/network-bytestring-0.1.214361/network-bytestring-0.1.2/dist/setup/Main.o
)
Linking 
/tmp/network-bytestring-0.1.214361/network-bytestring-0.1.2/dist/setup/setup
...
Configuring network-bytestring-0.1.2...
Preprocessing library network-bytestring-0.1.2...
Building network-bytestring-0.1.2...
[1 of 5] Compiling Network.Socket.ByteString.IOVec (
dist/build/Network/Socket/ByteString/IOVec.hs,
dist/build/Network/Socket/ByteString/IOVec.o )
[2 of 5] Compiling Network.Socket.ByteString.MsgHdr (
dist/build/Network/Socket/ByteString/MsgHdr.hs,
dist/build/Network/Socket/ByteString/MsgHdr.o )
[3 of 5] Compiling Network.Socket.ByteString.Internal (
Network/Socket/ByteString/Internal.hs,
dist/build/Network/Socket/ByteString/Internal.o )
[4 of 5] Compiling Network.Socket.ByteString (
Network/Socket/ByteString.hs, dist/build/Network/Socket/ByteString.o )

Network/Socket/ByteString.hs:66:32:
Module
`Network.Socket.Internal'
does not export
`throwSocketErrorIfMinus1RetryMayBlock'
cabal: Error: some packages failed to install:
network-bytestring-0.1.2 failed during the building phase. The exception was:
exit: ExitFailure 1
[...@mavlo network-data]$ cabal install network-bytestring
Resolving dependencies...
[1 of 1] Compiling Main (
/tmp/network-bytestring-0.1.215107/network-bytestring-0.1.2/Setup.hs,
/tmp/network-bytestring-0.1.215107/network-bytestring-0.1.2/dist/setup/Main.o
)
Linking 
/tmp/network-bytestring-0.1.215107/network-bytestring-0.1.2/dist/setup/setup
...
Configuring network-bytestring-0.1.2...
Preprocessing library network-bytestring-0.1.2...
Building network-bytestring-0.1.2...
[1 of 5] Compiling Network.Socket.ByteString.IOVec (
dist/build/Network/Socket/ByteString/IOVec.hs,
dist/build/Network/Socket/ByteString/IOVec.o )
[2 of 5] Compiling Network.Socket.ByteString.MsgHdr (
dist/build/Network/Socket/ByteString/MsgHdr.hs,
dist/build/Network/Socket/ByteString/MsgHdr.o )
[3 of 5] Compiling Network.Socket.ByteString.Internal (
Network/Socket/ByteString/Internal.hs,
dist/build/Network/Socket/ByteString/Internal.o )
[4 of 5] Compiling Network.Socket.ByteString (
Network/Socket/ByteString.hs, dist/build/Network/Socket/ByteString.o )

Network/Socket/ByteString.hs:66:32:
Module
`Network.Socket.Internal'
does not export
`throwSocketErrorIfMinus1RetryMayBlock'
cabal: Error: some packages failed to install:
network-bytestring-0.1.2 failed during the building phase. The exception was:
exit: ExitFailure 1
[...@mavlo network-data]$ ghc-pkg --version
GHC package manager version 6.10.2
[...@mavlo network-data]$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.10.2
[...@mavlo network-data]$ ghc-pkg list
/usr/local/lib/ghc-6.10.2/./package.conf:
Cabal-1.6.0.3, HUnit-1.2.0.3, QuickCheck-1.2.0.0, array-0.2.0.0,
base-3.0.3.1, base-4.1.0.0, bytestring-0.9.1.4, containers-0.2.0.1,
directory-1.0.0.3, (dph-base-0.3), (dph-par-0.3),
(dph-prim-interface-0.3), (dph-prim-par-0.3), (dph-prim-seq-0.3),
(dph-seq-0.3), editline-0.2.1.0, filepath-1.1.0.2, (ghc-6.10.2),
ghc-prim-0.1.0.0, haddock-2.4.2, haskell-src-1.0.1.3,
haskell98-1.0.1.0, hpc-0.5.0.3, html-1.0.1.2, integer-0.1.0.1,
mtl-1.1.0.2, network-2.2.1, old-locale-1.0.0.1, old-time-1.0.0.2,
packedstring-0.1.0.1, parallel-1.1.0.1, parsec-2.1.0.1,
pretty-1.0.1.0, process-1.0.1.1, random-1.0.0.1,
regex-base-0.72.0.2, regex-compat-0.71.0.1, regex-posix-0.72.0.3,
rts-1.0, stm-2.1.1.2, syb-0.1.0.1, template-haskell-2.3.0.1,
unix-2.3.2.0, xhtml-3000.2.0.1
/home/tom/.ghc/x86_64-linux-6.10.2/package.conf:
Control-Engine-0.0.4, binary-0.5, network-data-0.0.2,
prettyclass-1.0.0.0, pureMD5-0.2.4, time-1.1.2.3

On Sun, Apr 5, 2009 at 6:01 AM, Johan Tibell  wrote:
> I am pleased to announce a new release of network-bytestring, a Haskell 
> library
> for fast socket I/O using ByteStrings.
>
> New in this release is support for scatter/gather I/O (also known as
> vectored I/O). Scatter/gather I/O provides more efficient I/O by using
> one system call to send several separate pieces of data and by
> avoiding unnecessary copying.
>
> I would like to thank Brian Lewis, Bryan O'Sullivan, and Thomas
> Schilling for contributing patches for this release.
>
> Get it:
>
>   cabal install network-bytestring
>
> And on Hackage:
>
>   
> http://hackage.haskell.org/cgi-bin/hackage-scripts/package/network-bytestring
>
> Windows hackers needed:
>
>   I've made sure that the library builds on Windows but since I don't
> use Windows myself I haven't implemented scatter/gather I/O support
> for Windows. It should be straightforward to add and I

Re: [Haskell-cafe] Re: GHC: compile using multiple cores?

2009-04-09 Thread Andrea Vezzosi
The main bottleneck right now is that each ghc process has to read the
package.conf, which afaiu is done with Read and it's awfully slow,
especially if you have many packages installed.
I've started seeing total time improvements when approaching ~300% CPU
usage and only the extralibs installed.

On Thu, Apr 9, 2009 at 5:51 PM, Neil Mitchell  wrote:
>> Not with cabal, with GHC, yes: assuming you have enough modules. Use ghc
>> -M to dump a makefile, and then make -j20 (or whatever you have)
>
> There is a performance penalty to running ghc on separate files vs
> --make. If your number of core's is limited --make may be better. I'd
> love someone to figure out what the cross over point is :-)
>
> As a related question, how does GHC implement -j3? For my programs, if
> I want to run in parallel, I have to type +RTS -N3. Can I use the same
> trick as GHC?
>
> Thanks
>
> Neil
> ___
> 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] Re: GHC: compile using multiple cores?

2009-04-09 Thread Peter Verswyvelen
That should be fairly easy to optimize I guess? Maybe even using read-only
shared memory to share the parsed database in native binary format? On Fri,
Apr 10, 2009 at 1:08 AM, Andrea Vezzosi  wrote:

> The main bottleneck right now is that each ghc process has to read the
> package.conf, which afaiu is done with Read and it's awfully slow,
> especially if you have many packages installed.
> I've started seeing total time improvements when approaching ~300% CPU
> usage and only the extralibs installed.
>
> On Thu, Apr 9, 2009 at 5:51 PM, Neil Mitchell 
> wrote:
> >> Not with cabal, with GHC, yes: assuming you have enough modules. Use ghc
> >> -M to dump a makefile, and then make -j20 (or whatever you have)
> >
> > There is a performance penalty to running ghc on separate files vs
> > --make. If your number of core's is limited --make may be better. I'd
> > love someone to figure out what the cross over point is :-)
> >
> > As a related question, how does GHC implement -j3? For my programs, if
> > I want to run in parallel, I have to type +RTS -N3. Can I use the same
> > trick as GHC?
> >
> > Thanks
> >
> > Neil
> > ___
> > Haskell-Cafe mailing list
> > Haskell-Cafe@haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Referential Transparency and Monads

2009-04-09 Thread Brandon S. Allbery KF8NH

On 2009 Apr 9, at 16:09, Luke Palmer wrote:
On Thu, Apr 9, 2009 at 1:33 PM, Miguel Mitrofanov > wrote:

I'm not sure what you mean by that, but semantically IO is definitely
*not* a state monad.  Under any circumstances or any set of  
assumptions.


Ehm? Why not?

Mainly forkIO.  There may be other reasons.



I thought I had excluded that stuff to simplify the question; the fact  
that IO is Haskell's toxic waste dump is more or less irrelevant to  
the core concept.


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




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


Re: [Haskell-cafe] Referential Transparency and Monads

2009-04-09 Thread Jonathan Cast
On Thu, 2009-04-09 at 21:57 -0400, Brandon S. Allbery KF8NH wrote:
> On 2009 Apr 9, at 16:09, Luke Palmer wrote:
> > On Thu, Apr 9, 2009 at 1:33 PM, Miguel Mitrofanov
> >  wrote:
> > I'm not sure what you mean by that, but semantically
> > IO is definitely
> > *not* a state monad.  Under any circumstances or any
> > set of assumptions.
> > 
> > 
> > Ehm? Why not?
> > 
> > Mainly forkIO.  There may be other reasons.
> > 
> 
> 
> I thought I had excluded that stuff to simplify the question; the fact
> that IO is Haskell's toxic waste dump is more or less irrelevant to
> the core concept.

Well, the `core concept' of IO includes the concept of a user who's
watching and interacting with your program as it runs, no?

Say I know that a file named `/my_file' exists and is readable and
writeable and etc.  Now consider the program

  do
 s <- readFile "/my_file"
 writeFile "/my_file" "Hello, world!\n"
 threadDelay 1 -- If you don't like threadDelay, just substitute forcing
   -- an expensive thunk here
 writeFile "/my_file" s

As a function from initial state to final state, this program is just
the identity; but surely this program should be considered different
than just

  threadDelay 1

.  To give a meaningful semantics to IO, you have to consider the
intermediate state(s) the system goes through, where a state monad
denotation for IO would discard them.

jcc


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


Re: [Haskell-cafe] Referential Transparency and Monads

2009-04-09 Thread Jonathan Cast
On Thu, 2009-04-09 at 22:47 -0400, Brandon S. Allbery KF8NH wrote:
> On 2009 Apr 9, at 22:30, Jonathan Cast wrote:
> > On Thu, 2009-04-09 at 21:57 -0400, Brandon S. Allbery KF8NH wrote:
> >> On 2009 Apr 9, at 16:09, Luke Palmer wrote:
> >>> On Thu, Apr 9, 2009 at 1:33 PM, Miguel Mitrofanov
> >>>  wrote:
> >>>I'm not sure what you mean by that, but semantically
> >>>IO is definitely
> >>>*not* a state monad.  Under any circumstances or any
> >>>set of assumptions.
> >>>
> >>>Ehm? Why not?
> >>>
> >>> Mainly forkIO.  There may be other reasons.
> >>
> >> I thought I had excluded that stuff to simplify the question; the  
> >> fact
> >> that IO is Haskell's toxic waste dump is more or less irrelevant to
> >> the core concept.
> >
> > Well, the `core concept' of IO includes the concept of a user who's
> > watching and interacting with your program as it runs, no?
> 
> Yes.  That's the opaque "real world";  an I/O operation conceptually  
> modifies this state,

Pedantic nit-pick: modification is not referentially transparent.  You
mean `returns a modified copy'.

> which is how things get tied together.  Ordinary  
> user programs can't interact with the "real world" sate except via  
> functions defined on IO, which are assumed to modify the state; that's  
> exactly how non-RT actions are modeled via RT code.
> 
> Stuff like forkIO and newIORef can also be understood that way, it's  
> just a bit more complex to follow them around.
> 
> Please note that ghc *does* implement IO (from Core up, at least) this  
> way, modulo unboxed tuples, so claims that it is "wrong" are dubious  
> at best.

No, GHC implements IO using an internal side-effectful language.  (Note
that the `state' IO uses internally is an (un-boxed and un-pointed)
0-bit word!  It certainly doesn't have enough semantic content
to /actually/ contain the entire state of the computer.)  The difference
between GHC core and a truly referentially transparent language is that
you can't implement unsafePerformIO unless your language has side
effects.

Oh, and I should have cited Tackling the Awkward Squad as the source of
my dubious claim.

> > s <- readFile "/my_file"
> > writeFile "/my_file" "Hello, world!\n"
> > threadDelay 1 -- If you don't like threadDelay, just  
> > substitute forcing
> >   -- an expensive thunk here
> > writeFile "/my_file" s
> >
> > As a function from initial state to final state, this program is just
> > the identity; but surely this program should be considered different
> 
> It is?
> 
>  > -- these implicitly are considered to return a modified RealWorld
>  > readFile :: RealWorld -> (String,RealWorld)
>  > writeFile :: RealWorld -> ((),RealWorld)
>  > threadDelay :: RealWorld -> ((),RealWorld)
>  >
>  > main :: RealWorld -> ((),RealWorld)
>  > main state =
>  >   case readFile state "/my_file" of
>  > (s,state') ->
>  >case writeFile state' "/my_file" "Hello, world!\n" of
>  >  (_,state'') ->
>  > case threadDelay state'' 1 of
>  >   (_,state'') -> writeFile "/my_file" s state''

(This has arguments very much in the wrong order throughout, of course.)

> This is just the State monad, unwrapped.

What on earth does that have to do with anything?  If I change your last
line to

> (_,state''') -> case writeFile "/my_file" s state''' of
>(x, state) -> (x, state)

Then I can observe that state, if it really names the current state
of the system as of the program's finish-point, is exactly equivalent to
state (e.g., in both states every file has exactly the same contents).
(The only difference, which I forgot, is that the current time is >
10sec later than in state.  Doesn't affect the point.)

Now, the *definition* you gave is, in form, different than the
definition of

  threadDelay 1

However, the point of referential transparency is that you can inline
the definitions of readFile and writeFile into the scrutinees of your
case statements, and then (possibly after something like a case-of-case
transformation) you can eliminate the case expressions and intermediate
states and get something like:

  \ (!state) -> let
  s = fileContents "/my_file" state
in case threadDelay 1 state of
 (_, state') ->
   ((), setFileContents "/my_file" s state')

where, since threadDelay has no side effects but increasing the current
time, 

 fileContents "/my_file" state'
  == fileContents "/my_file" state

so the above is equivalent to

  \ (!state) -> case threadDelay 1 state of
   (_, state') ->
 ((), setFileContents "/my_file" (fileContents "/my_file"
state') state')

but obviously

 setFileContents fn (fileContents fn state') state'
  == state'

so therefore the above is equivalent to

  \ (!state) -> case threadDelay 1 state of
   

Re: [Haskell-cafe] How to define a common return and bind?

2009-04-09 Thread Iavor Diatchki
Hi,
You can do things like that for "new" monads that are isomorphic to
existing ones.  Take a look at the MonadLib.Derive package from
MonadLib 
(http://hackage.haskell.org/packages/archive/monadLib/3.5.2/doc/html/MonadLib-Derive.html).
 More specifically, the functions "derive_return" and "derive_bind"
might be of interest.  A more general property for monad transformers
is that you can always define the "return" of the new monad in terms
of the "return" of the underlying monad and "lift":

return_new x = lift (return x)

This works because, in general, "lift" should be a "monad morphism".

Hope that this helps,
Iavor


On Thu, Apr 9, 2009 at 3:40 AM, Bas van Dijk  wrote:
> Hello,
>
> Suppose you have defined a monad transformer such as:
>
>> newtype T1 m a = T1 { unT1 :: A1 m a }
>
> Where 'A1 m' is an arbitrary monad of your choosing.
> For this discussion we just take the identity:
>
>> type A1 m a = m a   -- (can be any monad)
>
> If you want to define a Monad instance for 'T1 m' you generally do this:
>
> instance Monad m => Monad (T1 m) where
>    return  = T1 . return
>    m >>= f = T1 $ unT1 m >>= unT1 . f
>
> (I know I can use the 'GeneralizedNewtypeDeriving' language extension
> to automatically derive a Monad but suppose that isn't available)
>
> Now when I define a new monad transformer:
>
>> newtype T2 m a = T2 { unT2 :: A2 m a }
>
> Where 'A2 m' is again an arbitrary monad of your choosing but for now
> just the identity:
>
>> type A2 m a = m a   -- (can be any monad)
>
> The Monad instance for it is almost completely identical to the former:
>
> instance Monad m => Monad (T2 m) where
>    return  = T2 . return
>    m >>= f = T2 $ unT2 m >>= unT2 . f
>
> Note that the only differences are:
>
>  * a function to convert
>   from the outer monad _to_ the inner monad:
>   'unT1' and 'unT2'
>
>  * a function to convert
>   _from_ the inner monad to the outer monad:
>   'T1' and 'T2'
>
> The common parts seem to be:
>
> liftReturn from = from . return
> liftBind   from to m f = from $ to m >>= to . f
>
> My question is: can these be given suitable and general enough types
> so that they can be used to define Monad instances for monad
> transformers?
>
> In other words can I use them to write:
>
> instance Monad m => Monad (T1 m) where
>    return = liftReturn T1
>    (>>=)  = liftBind   T1 unT1
>
> and:
>
> instance Monad m => Monad (T2 m) where
>    return = liftReturn T2
>    (>>=)  = liftBind   T2 unT2
>
> Thanks,
>
> Bas
> ___
> 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] Referential Transparency and Monads

2009-04-09 Thread Brandon S. Allbery KF8NH

On 2009 Apr 9, at 22:30, Jonathan Cast wrote:

On Thu, 2009-04-09 at 21:57 -0400, Brandon S. Allbery KF8NH wrote:

On 2009 Apr 9, at 16:09, Luke Palmer wrote:

On Thu, Apr 9, 2009 at 1:33 PM, Miguel Mitrofanov
 wrote:
   I'm not sure what you mean by that, but semantically
   IO is definitely
   *not* a state monad.  Under any circumstances or any
   set of assumptions.

   Ehm? Why not?

Mainly forkIO.  There may be other reasons.


I thought I had excluded that stuff to simplify the question; the  
fact

that IO is Haskell's toxic waste dump is more or less irrelevant to
the core concept.


Well, the `core concept' of IO includes the concept of a user who's
watching and interacting with your program as it runs, no?


Yes.  That's the opaque "real world";  an I/O operation conceptually  
modifies this state, which is how things get tied together.  Ordinary  
user programs can't interact with the "real world" sate except via  
functions defined on IO, which are assumed to modify the state; that's  
exactly how non-RT actions are modeled via RT code.


Stuff like forkIO and newIORef can also be understood that way, it's  
just a bit more complex to follow them around.


Please note that ghc *does* implement IO (from Core up, at least) this  
way, modulo unboxed tuples, so claims that it is "wrong" are dubious  
at best.

s <- readFile "/my_file"
writeFile "/my_file" "Hello, world!\n"
threadDelay 1 -- If you don't like threadDelay, just  
substitute forcing

  -- an expensive thunk here
writeFile "/my_file" s

As a function from initial state to final state, this program is just
the identity; but surely this program should be considered different


It is?

> -- these implicitly are considered to return a modified RealWorld
> readFile :: RealWorld -> (String,RealWorld)
> writeFile :: RealWorld -> ((),RealWorld)
> threadDelay :: RealWorld -> ((),RealWorld)
>
> main :: RealWorld -> ((),RealWorld)
> main state =
>   case readFile state "/my_file" of
> (s,state') ->
>case writeFile state' "/my_file" "Hello, world!\n" of
>  (_,state'') ->
> case threadDelay state'' 1 of
>   (_,state'') -> writeFile "/my_file" s   

This is just the State monad, unwrapped.  And the differences between  
this and the actual GHC implementation are the use of unboxed tuples  
and RealWorld actually being a type that can't be accessed by normal  
Haskell code.


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




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


Re: [Haskell-cafe] Referential Transparency and Monads

2009-04-09 Thread Brandon S. Allbery KF8NH

On 2009 Apr 9, at 22:47, Brandon S. Allbery KF8NH wrote:

> -- these implicitly are considered to return a modified RealWorld
> readFile :: RealWorld -> (String,RealWorld)
> writeFile :: RealWorld -> ((),RealWorld)
> threadDelay :: RealWorld -> ((),RealWorld)
>
> main :: RealWorld -> ((),RealWorld)
> main state =
>   case readFile state "/my_file" of
> (s,state') ->
>case writeFile state' "/my_file" "Hello, world!\n" of
>  (_,state'') ->
> case threadDelay state'' 1 of
>   (_,state'') -> writeFile "/my_file" s   


Sorry, the last line should be:

>   (_,state''') -> writeFile state''' "/my_file" s

This code is nothing more nor less than the translation of Jonathan  
Cast's code, using a presumptive


> type IO a = State RealWorld a

into "linear" de-monadified code.  Clearly the state is threaded into  
main, through all the calls, and the final state returned; the state  
threading is what maintains the referentially transparent model.


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




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


Re: [Haskell-cafe] Referential Transparency and Monads

2009-04-09 Thread Miguel Mitrofanov


On 10 Apr 2009, at 06:30, Jonathan Cast wrote:

 do
s <- readFile "/my_file"
writeFile "/my_file" "Hello, world!\n"
threadDelay 1 -- If you don't like threadDelay, just  
substitute forcing

  -- an expensive thunk here
writeFile "/my_file" s

As a function from initial state to final state, this program is just
the identity;


No, since world state includes the user state itself, not just files  
contents.

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


Re: [Haskell-cafe] Referential Transparency and Monads

2009-04-09 Thread Luke Palmer
On Thu, Apr 9, 2009 at 8:47 PM, Brandon S. Allbery KF8NH <
allb...@ece.cmu.edu> wrote:

> Yes.  That's the opaque "real world";  an I/O operation conceptually
> modifies this state, which is how things get tied together.  Ordinary user
> programs can't interact with the "real world" sate except via functions
> defined on IO, which are assumed to modify the state; that's exactly how
> non-RT actions are modeled via RT code.
>
> Stuff like forkIO and newIORef can also be understood that way, it's just a
> bit more complex to follow them around.


newIORef is trivial: just keep a unique counter in the state.

Have you tried forkIO?  I used to think that "world passing" was an
acceptable, if ugly, semantics for IO.  However, after doing some formal
modeling, I realized that forkIO breaks the model altogether.  What happens
to the end state of the forked thread?

If it really is thought of that way, surely you will be able to create a
pure IO simulator as a state monad (for an arbitrarily complex world) that
handles only forkIO, threadDelay, and print  (just using a write buffer).
 Think about that for a second.

Luke



>
>
> Please note that ghc *does* implement IO (from Core up, at least) this way,
> modulo unboxed tuples, so claims that it is "wrong" are dubious at best.
>
>>s <- readFile "/my_file"
>>writeFile "/my_file" "Hello, world!\n"
>>threadDelay 1 -- If you don't like threadDelay, just substitute
>> forcing
>>  -- an expensive thunk here
>>writeFile "/my_file" s
>>
>> As a function from initial state to final state, this program is just
>> the identity; but surely this program should be considered different
>>
>
> It is?
>
> > -- these implicitly are considered to return a modified RealWorld
> > readFile :: RealWorld -> (String,RealWorld)
> > writeFile :: RealWorld -> ((),RealWorld)
> > threadDelay :: RealWorld -> ((),RealWorld)
> >
> > main :: RealWorld -> ((),RealWorld)
> > main state =
> >   case readFile state "/my_file" of
> > (s,state') ->
> >case writeFile state' "/my_file" "Hello, world!\n" of
> >  (_,state'') ->
> > case threadDelay state'' 1 of
> >   (_,state'') -> writeFile "/my_file" s
>
> This is just the State monad, unwrapped.  And the differences between this
> and the actual GHC implementation are the use of unboxed tuples and
> RealWorld actually being a type that can't be accessed by normal Haskell
> code.
>
> --
> brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
> system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
> electrical and computer engineering, carnegie mellon universityKF8NH
>
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Referential Transparency and Monads

2009-04-09 Thread Brandon S. Allbery KF8NH

On 2009 Apr 10, at 0:14, Luke Palmer wrote:
On Thu, Apr 9, 2009 at 8:47 PM, Brandon S. Allbery KF8NH > wrote:
Stuff like forkIO and newIORef can also be understood that way, it's  
just a bit more complex to follow them around.


Have you tried forkIO?  I used to think that "world passing" was an  
acceptable, if ugly, semantics for IO.  However, after doing some  
formal modeling, I realized that forkIO breaks the model  
altogether.  What happens to the end state of the forked thread?


What happens to it when main returns?  When you fork a subprocess, and  
when it exits?  Same answer, although it might be better modeled as  
passing a reference to the RealWorld around to model independent  
threads all doing I/O (at least, I don't *think* forkIO is just a  
funny-looking unsafeInterleaveIO).  In any case, threads and process  
forks do complicate things but could be emulated if I wanted to go to  
the effort of implementing green threads in single-threaded Haskell  
code; the RealWorld is the least of the problems introduced, it's best  
thought of as cloning part (threads) or all (processes) of the  
program's own state, which is *also* conceptually contained in the  
RealWorld.


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




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


[Haskell-cafe] Re: Referential Transparency and Monads

2009-04-09 Thread Heinrich Apfelmus
Luke Palmer wrote:
> Miguel Mitrofanov wrote:
> 
>> I'm not sure what you mean by that, but semantically IO is definitely
>>> *not* a state monad.  Under any circumstances or any set of assumptions.
>>>
>> Ehm? Why not?
> 
> 
> Mainly forkIO.  There may be other reasons.

"Tackling the awkward squad" mentions that

  loop  :: IO ()
  loop  = loop

and

  loop' :: IO ()
  loop' = putStr "o" >> loop'

are indistinguishable in the

  IO a  ~  World -> (a, World)

semantics. Both expressions would be _|_. But clearly, the latter
produces some output while the former just hangs.


Regards,
apfelmus

--
http://apfelmus.nfshost.com

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


Re: [Haskell-cafe] Re: Referential Transparency and Monads

2009-04-09 Thread Brandon S. Allbery KF8NH

On 2009 Apr 10, at 0:33, Heinrich Apfelmus wrote:

Luke Palmer wrote:

Miguel Mitrofanov wrote:

I'm not sure what you mean by that, but semantically IO is  
definitely
*not* a state monad.  Under any circumstances or any set of  
assumptions.



Ehm? Why not?


Mainly forkIO.  There may be other reasons.

 loop' :: IO ()
 loop' = putStr "o" >> loop'

are indistinguishable in the

 IO a  ~  World -> (a, World)



I still don't understand this; we are passing a World and getting a  
World back, *conceptually* the returned World is modified by putStr.   
It's not in reality, but we get the same effects if we write to a  
buffer and observe that buffer with a debugger --- state threading  
constrains the program to the rules that must be followed for ordered  
I/O, which is what matters.


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




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


Re: [Haskell-cafe] Re: Referential Transparency and Monads

2009-04-09 Thread Jonathan Cast
On Fri, 2009-04-10 at 00:46 -0400, Brandon S. Allbery KF8NH wrote:
> On 2009 Apr 10, at 0:33, Heinrich Apfelmus wrote:
> > Luke Palmer wrote:
> >> Miguel Mitrofanov wrote:
> >>
> >>> I'm not sure what you mean by that, but semantically IO is  
> >>> definitely
>  *not* a state monad.  Under any circumstances or any set of  
>  assumptions.
> 
> >>> Ehm? Why not?
> >>
> >> Mainly forkIO.  There may be other reasons.
> >  loop' :: IO ()
> >  loop' = putStr "o" >> loop'
> >
> > are indistinguishable in the
> >
> >  IO a  ~  World -> (a, World)
> 
> 
> I still don't understand this; we are passing a World and getting a  
> World back,

We are?  Why do you think that?

jcc


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


Re: [Haskell-cafe] Referential Transparency and Monads

2009-04-09 Thread Jonathan Cast
On Fri, 2009-04-10 at 07:29 +0400, Miguel Mitrofanov wrote:
> On 10 Apr 2009, at 06:30, Jonathan Cast wrote:
> >  do
> > s <- readFile "/my_file"
> > writeFile "/my_file" "Hello, world!\n"
> > threadDelay 1 -- If you don't like threadDelay, just  
> > substitute forcing
> >   -- an expensive thunk here
> > writeFile "/my_file" s
> >
> > As a function from initial state to final state, this program is just
> > the identity;
> 
> No, since world state includes the user state itself, not just files  
> contents.

My programs are passing me around inside a state token?

jcc


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


Re: [Haskell-cafe] Re: Referential Transparency and Monads

2009-04-09 Thread Brandon S. Allbery KF8NH

On 2009 Apr 10, at 0:52, Jonathan Cast wrote:

On Fri, 2009-04-10 at 00:46 -0400, Brandon S. Allbery KF8NH wrote:

IO a  ~  World -> (a, World)


I still don't understand this; we are passing a World and getting a
World back,


We are?  Why do you think that?


Because that's what (World -> (a,World)) means, last I checked.

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




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


Re: [Haskell-cafe] Referential Transparency and Monads

2009-04-09 Thread Brandon S. Allbery KF8NH

On 2009 Apr 10, at 1:00, Jonathan Cast wrote:

On Fri, 2009-04-10 at 07:29 +0400, Miguel Mitrofanov wrote:

On 10 Apr 2009, at 06:30, Jonathan Cast wrote:

do
   s <- readFile "/my_file"
   writeFile "/my_file" "Hello, world!\n"
   threadDelay 1 -- If you don't like threadDelay, just
substitute forcing
 -- an expensive thunk here
   writeFile "/my_file" s

As a function from initial state to final state, this program is  
just

the identity;


No, since world state includes the user state itself, not just files
contents.


My programs are passing me around inside a state token?



You seem to have redefined "conceptually" to mean "in absolute  
literalness".


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




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


Re: [Haskell-cafe] Re: Referential Transparency and Monads

2009-04-09 Thread Jonathan Cast
On Fri, 2009-04-10 at 01:03 -0400, Brandon S. Allbery KF8NH wrote:
> On 2009 Apr 10, at 0:52, Jonathan Cast wrote:
> > On Fri, 2009-04-10 at 00:46 -0400, Brandon S. Allbery KF8NH wrote:
> >>> IO a  ~  World -> (a, World)
> >>
> >> I still don't understand this; we are passing a World and getting a
> >> World back,
> >
> > We are?  Why do you think that?
> 
> Because that's what (World -> (a,World)) means, last I checked.

Does

undefined :: (a, World)

contain a World?

jcc


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


Re: [Haskell-cafe] Re: Referential Transparency and Monads

2009-04-09 Thread Brandon S. Allbery KF8NH

On 2009 Apr 10, at 1:09, Jonathan Cast wrote:

On Fri, 2009-04-10 at 01:03 -0400, Brandon S. Allbery KF8NH wrote:

On 2009 Apr 10, at 0:52, Jonathan Cast wrote:

On Fri, 2009-04-10 at 00:46 -0400, Brandon S. Allbery KF8NH wrote:

IO a  ~  World -> (a, World)


I still don't understand this; we are passing a World and getting a
World back,


We are?  Why do you think that?


Because that's what (World -> (a,World)) means, last I checked.


Does

   undefined :: (a, World)

contain a World?


Does

> undefined :: Sum Int

contain an Int?  Please use some common sense, your recent responses  
are increasingly incoherent.


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




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


Re: [Haskell-cafe] Re: WX: linking to system libraries statically

2009-04-09 Thread Jason Dusek
2009/04/09 FFT :
> I noticed that even simple WX demos like "Layout" are linked
> dynamically against 59 libraries on Linux. This would make
> distributing the binaries a nightmare. Is there a simple way
> to make a (mostly) statically linked binary?

  I have had mixed success with `-static -optl-static` (as
  recommended in "Practical Web Programming in Haskell" page,
  for example). On Macs, it's hard to get it to work (have never
  bothered); on Linux, I remember I had to remove it on once
  occasion to get things to work across Ubuntu and Gentoo (had
  to do with differences in libc, I believe, but I did not
  retain notes).

  Maybe passing in the specific libs to the linker with `-optl`
  is the best bet?

--
Jason Dusek


 |...Practical Web Programming in Haskell...|
  
http://www.haskell.org/haskellwiki/Practical_web_programming_in_Haskell#Compiling_and_running_web_applications
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Sequence differences

2009-04-09 Thread michael rice
I have a Scheme function that calculates sequence differences, i.e., it returns 
a sequence that is the difference between the 2nd and the 1st element, the 3rd 
and the 2nd, the 4th and the 3rd, etc.

(define s
  (lambda (f l)
    (cond ((null? (cdr l)) '())
  (else (cons (f (cadr l) (car l))
  (s f (cdr l)))

where

(s - '(0,1,3,6,10,15,21,28)) => (1,2,3,4,5,6,7)


I'm thinking the same function in Haskell would be something like

s :: 
s f [] = []
s f [x] = [x] 
s f l = [ a f b | (a,b) <- zip (init l) (tail l)]


but can't figure out what the function typing would be.

Michael




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


Re: [Haskell-cafe] Sequence differences

2009-04-09 Thread Joe Fredette

So, we can walk through it-

> s f [] = []
> s f [x] = [x]
> s f l = [ a f b | (a,b) <- zip (init l) (tail l)]

First, we can write some of it to be a little more idiomatic, viz:

s _ []  = []
s _ [x] = [x]
s f ls  = [f a b | (a,b) <- zip (init ls) (tail ls)]

First, we have a function type, we can tell the variable f is a function 
because it's applied to arguments in the third case, since it's applied 
to two arguments, it's binary, so `s :: (a -> b -> c) -> ?` however, 
from the
second case, we know that whatever the type of the second argument (a 
list of some type `a1`) is also the type
of the return argument, since the `s` acts as the identity for lists of 
length less than 2, so


   s :: (a -> b -> a1) -> [a1] -> [a1]

However, since the arguments for `f` are drawn from the same list, the 
argument types must _also_ be of type `a1`, leaving us with:


   s :: (a -> a -> a) -> [a] -> [a]

This is, interestingly enough, precisely the type of foldr1.

We can write your original function in another, cleaner way though, too, 
since zip will "zip" to the smaller of the two lengths, so you don't 
need to worry about doing the init and the tail, so `s` is really:


s _ []  = []
s _ [x] = [x]
s f ls  = [f a b | (a,b) <- zip ls (tail ls)]

but there is a function which does precisely what the third case does, 
called "zipWith" which takes a
binary function and two lists and -- well -- does what that list 
comprehension does. In fact, it does
what your whole function does... In fact, it _is_ your function, 
specialized a little, eg:


yourZipWith f ls = zipWith f ls (tail ls)


Hope that helps

/Joe

michael rice wrote:
I have a Scheme function that calculates sequence differences, i.e., 
it returns a sequence that is the difference between the 2nd and the 
1st element, the 3rd and the 2nd, the 4th and the 3rd, etc.


(define s
  (lambda (f l)
(cond ((null? (cdr l)) '())
  (else (cons (f (cadr l) (car l))
  (s f (cdr l)))

where

(s - '(0,1,3,6,10,15,21,28)) => (1,2,3,4,5,6,7)


I'm thinking the same function in Haskell would be something like

s ::
s f [] = []
s f [x] = [x]
s f l = [ a f b | (a,b) <- zip (init l) (tail l)]


but can't figure out what the function typing would be.

Michael




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
  
begin:vcard
fn:Joseph Fredette
n:Fredette;Joseph
adr:Apartment #3;;6 Dean Street;Worcester;Massachusetts;01609;United States of America
email;internet:jfred...@gmail.com
tel;home:1-508-966-9889
tel;cell:1-508-254-9901
x-mozilla-html:FALSE
url:lowlymath.net, humbuggery.net
version:2.1
end:vcard

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


[Haskell-cafe] Re: Referential Transparency and Monads

2009-04-09 Thread Heinrich Apfelmus
Brandon S. Allbery wrote:
> Heinrich Apfelmus wrote:
>
>>  loop' :: IO ()
>>  loop' = putStr "o" >> loop'
>>
>> are indistinguishable in the
>>
>>  IO a  ~  World -> (a, World)
> 
> 
> I still don't understand this; we are passing a World and getting a
> World back, *conceptually* the returned World is modified by putStr. 
> It's not in reality, but we get the same effects if we write to a buffer
> and observe that buffer with a debugger --- state threading constrains
> the program to the rules that must be followed for ordered I/O, which is
> what matters.

Basically, the problem is that neither computation returns the final
World because neither one terminates.

More precisely, the goal of the

IO a  ~  World -> (a, World)

semantics is to assign each expression of type  IO a  a pure function
World -> (a, World) . For instance, the expression

putChar 'c'

would be assigned a function

\world -> ((), world where 'c' has been printed)

or similar.

Now, the problem is that both  loop  and  loop'  are being assigned the
same semantic function

loop   ~  \world -> _|_
loop'  ~  \world -> _|_

We can't distinguish between a function that mutilates the world and
then doesn't terminate and a function that is harmless but doesn't
terminate either. After all, both return the same result (namely _|_)
for the same input worlds.


Regards,
apfelmus

--
http://apfelmus.nfshost.com

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


Re: [Haskell-cafe] Re: Referential Transparency and Monads

2009-04-09 Thread minh thu
2009/4/10 Heinrich Apfelmus :
> Brandon S. Allbery wrote:
>> Heinrich Apfelmus wrote:
>>
>>>  loop' :: IO ()
>>>  loop' = putStr "o" >> loop'
>>>
>>> are indistinguishable in the
>>>
>>>  IO a  ~  World -> (a, World)
>>
>>
>> I still don't understand this; we are passing a World and getting a
>> World back, *conceptually* the returned World is modified by putStr.
>> It's not in reality, but we get the same effects if we write to a buffer
>> and observe that buffer with a debugger --- state threading constrains
>> the program to the rules that must be followed for ordered I/O, which is
>> what matters.
>
> Basically, the problem is that neither computation returns the final
> World because neither one terminates.
>
> More precisely, the goal of the
>
>IO a  ~  World -> (a, World)
>
> semantics is to assign each expression of type  IO a  a pure function
> World -> (a, World) . For instance, the expression
>
>putChar 'c'
>
> would be assigned a function
>
>\world -> ((), world where 'c' has been printed)
>
> or similar.
>
> Now, the problem is that both  loop  and  loop'  are being assigned the
> same semantic function
>
>loop   ~  \world -> _|_
>loop'  ~  \world -> _|_
>
> We can't distinguish between a function that mutilates the world and
> then doesn't terminate and a function that is harmless but doesn't
> terminate either. After all, both return the same result (namely _|_)
> for the same input worlds.

I'm not sure I follow.

> ones = 1:ones

is similar to loop or loop' but I can 'take 5' from it.

Even if loop or loop' do not terminate, some value is produced, isn't it ?

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