Re: [Haskell-cafe] An experimental Zipper using Thrists and first-class Labels. Help or thoughts?

2010-07-27 Thread Jason Dagit
On Mon, Jul 26, 2010 at 10:59 PM, Jason Dagit da...@codersbase.com wrote:


  ($) is application, but in the space of functions it is identity.  So, if
 you think the elements in your thrist as being values in the space of
 functions, you're asking for a right fold that is like, v1 `id` (v2 `id` (v3
 `id` ...), which I hope you agree doesn't make that much sense.


I just realized a better way to phrase this analogy is that id and ($) are
0, and (.) is (+).

So your foldr expands like:
v1 `0` (v2 `0` (v3 `0`  (vn `0` 0) ... )

But if you use (.), it expands like:
v1 + (v2 + (v3 + ... (vn + 0) ... )

I guess you could pick id = ($) = 1, and (.) = (*).  I think the analogy
works equally well, but I might be forgetting something simple.  Either way,
I bet you get what I'm rambling about so I'll stop now :)

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


Re: [Haskell-cafe] Re: ANN: weighted-regexp-0.1.0.0

2010-07-27 Thread Sjoerd Visscher

On Jul 27, 2010, at 7:09 AM, Sebastian Fischer wrote:
 I find 
 
  eachOnce :: [RegExp c] - RegExp c 
  eachOnce = foldr alt noMatch . map (foldr seq_ eps) . permutations 
 
 even clearer but your version is *much* better as it uses nesting to   
 combine all alternatives that start with the same regexp.

Yes, this was what I had at first too, but trying to match this on 8 items 
takes 2 seconds and 9 items already takes one minute.
--
Sjoerd Visscher
http://w3future.com




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


Re: [Haskell-cafe] Re: ANN: weighted-regexp-0.1.0.0

2010-07-27 Thread Sjoerd Visscher

On Jul 27, 2010, at 7:09 AM, Sebastian Fischer wrote:

 I'll add
 
noMatch :: RegExp c
noMatch = psym [] (const False)

Oh, by the way, with noMatch, eps, alt and seq_ RegExp is itself a Semiring, 
but I'm not sure what that would do.
--
Sjoerd Visscher
http://w3future.com




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


Re: [Haskell-cafe] Re: ANN: weighted-regexp-0.1.0.0

2010-07-27 Thread Eugene Kirpichov
Perhaps this might mean that we can get incremental and parallel
regexp matching by associating each character with a linear operator
(matrix) over this or related semiring, or something, and mixing that
with two sigfpe's articles:
http://blog.sigfpe.com/2008/11/approach-to-algorithm-parallelisation.html
http://blog.sigfpe.com/2009/01/fast-incremental-regular-expression.html

2010/7/27 Sjoerd Visscher sjo...@w3future.com:

 On Jul 27, 2010, at 7:09 AM, Sebastian Fischer wrote:

 I'll add

    noMatch :: RegExp c
    noMatch = psym [] (const False)

 Oh, by the way, with noMatch, eps, alt and seq_ RegExp is itself a Semiring, 
 but I'm not sure what that would do.
 --
 Sjoerd Visscher
 http://w3future.com




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




-- 
Eugene Kirpichov
Senior Software Engineer,
Grid Dynamics http://www.griddynamics.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] monoids and monads

2010-07-27 Thread Henning Thielemann
John Lato schrieb:
 Hello,
 
 I was wondering today, is this generally true?
 
 instance (Monad m, Monoid a) = Monoid (m a) where
   mempty = return mempty
   mappend = liftM2 mappend
 
 I know it isn't a good idea to use this instance, but assuming that
 the instance head does what I mean, is it valid?  Or more generally is
 it true for applicative functors as well?  I think it works for a few
 tricky monads, but that's not any sort of proof.  I don't even know
 how to express what would need to be proven here.

I translate 'valid' and 'true' to Is 'm a' a Monoid, given that 'm' is
a Monad and 'a' is a Monoid? If this is the question then we have to
show the Monoid laws for (m a), namely

left identity:   forall x. mappend mempty x = x
right identity:  forall x. mappend x mempty = x
associativity:
   forall x y z.
  (x `mappend` y) `mappend` z = x `mappend` (y `mappend` z)

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


[Haskell-cafe] ANN: weighted-regexp-0.1.1.0

2010-07-27 Thread Sebastian Fischer

I have released weighted-regexp-0.1.1.0 with two additional combinators:

-- | Does not match anything. 'noMatch' is an identity for 'alt'.
--
noMatch :: RegExp c

-- |
-- Matches a sequence of the given regular expressions in any
-- order. For example, the regular expression
--
-- @
-- perm (map char \abc\)
-- @
--
-- has the same meaning as
--
-- @
-- abc|acb|bcc|bac|cba|cab
-- @
--
-- and is represented as
--
-- @
-- a(bc|cb)|b(ca|ac)|c(ba|ab)
-- @
--
perm :: [RegExp c] - RegExp c

Cheers,
Sebastian


--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



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


Re: [Haskell-cafe] Is 'flip' really necessary?

2010-07-27 Thread Yves Parès
(??) is misleading, some may be tempted to write things like: func ?? 45 ??
x , forgetting that ?? is just a mere operator, not a syntactic convenience.
Unfortunately, Haskell doesn't provide Scala's underscore for partially
applied functions: func(56, _, foo, _)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: ANN: weighted-regexp-0.1.0.0

2010-07-27 Thread Sebastian Fischer


On Jul 27, 2010, at 9:15 AM, Sjoerd Visscher wrote:

Oh, by the way, with noMatch, eps, alt and seq_ RegExp is itself a  
Semiring,


Yes, but it's hard to define an Eq instance for arbitrary regular  
expressions that reflects equivalence of regexps.


There is currently only `instance Eq (RegExp Char)` which implements  
structural identity used for the QuickCheck tests.



but I'm not sure what that would do.


I think matching a regular expression against a word in the regular  
expressions semiring returns an unfolding of the original regular  
expression which matches exactly the given word.


Sebastian


--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



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


[Haskell-cafe] Re: Announce snm-0.0.2: Oops

2010-07-27 Thread Johnny Morrice
 Sorry if I have left typos, it's very late

I knew it was a bit late to be uploading things, I forgot to say where
anyone interested might download this:  

it's on Hackage so just 

cabal install snm

Cheers
   Johnny



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


[Haskell-cafe] Re: Instances for Set of Functor, Traversable?

2010-07-27 Thread oleg

Lennart Augustsson wrote:
 Try to make Set an instance of Functor and you'll see why it isn't.
 It's very annoying.

And yet the very simple, and old solution works. 

http://okmij.org/ftp/Haskell/types.html#restricted-datatypes

We just properly generalize Functor, so that all old functors are new
functors. In addition, many more functors become possible, including
Set. In general, we can have functors
fmap' :: (C1 a, C2 b) = (a - b) - f a - f b
Incidentally, even an Integer may be considered a functor: 
we can define the fmap' operation fitting the above signature, where
the constraint C1 a is a ~ Integer. 

Although the use of OverlappingInstances is not required, the
extension leads to the nicest code; all old functors just work.


{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}
{-# LANGUAGE OverlappingInstances #-}

module FunctorEx where

import Control.Monad
import Data.Set as S

class Functor' f a b where
fmap' :: (a - b) - f a - f b

-- The default instance:
-- All ordinary Functors are also extended functors

instance Functor f = Functor' f a b where
fmap' = fmap

-- Now define a functor for a set
instance (Ord a, Ord b) = Functor' S.Set a b where
fmap' = S.map


-- Define a degenerate functor, for an integer
newtype I a = I Integer deriving Show

instance Functor'  I Integer Integer where
fmap' f (I x) = I $ f x

-- tests

-- Lists as functors
test_l = fmap' (+10) [1,2,3,4]
-- [11,12,13,14]

-- Sets as functors
test_s = fmap' (\x - x `mod` 3) $ S.fromList [1,2,3,4]
-- fromList [0,1,2]

-- Integer as functor
test_i = fmap' (* (6::Integer)) $ I 7
-- I 42


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


Re: [Haskell-cafe] Re: Instances for Set of Functor, Traversable?

2010-07-27 Thread Lennart Augustsson
But that's not really a solution, since it doesn't make a Functor
instance for Set; it makes a Functor' instance for Set.
If you are willing to not be upwards compatible then, yes, there are solutions.

I think the best bet for an upwards compatible solutions is the
associated constraints,
www.cs.kuleuven.be/~toms/Research/papers/constraint_families.pdf

On Tue, Jul 27, 2010 at 10:17 AM,  o...@okmij.org wrote:

 Lennart Augustsson wrote:
 Try to make Set an instance of Functor and you'll see why it isn't.
 It's very annoying.

 And yet the very simple, and old solution works.

        http://okmij.org/ftp/Haskell/types.html#restricted-datatypes

 We just properly generalize Functor, so that all old functors are new
 functors. In addition, many more functors become possible, including
 Set. In general, we can have functors
        fmap' :: (C1 a, C2 b) = (a - b) - f a - f b
 Incidentally, even an Integer may be considered a functor:
 we can define the fmap' operation fitting the above signature, where
 the constraint C1 a is a ~ Integer.

 Although the use of OverlappingInstances is not required, the
 extension leads to the nicest code; all old functors just work.


 {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}
 {-# LANGUAGE OverlappingInstances #-}

 module FunctorEx where

 import Control.Monad
 import Data.Set as S

 class Functor' f a b where
    fmap' :: (a - b) - f a - f b

 -- The default instance:
 -- All ordinary Functors are also extended functors

 instance Functor f = Functor' f a b where
    fmap' = fmap

 -- Now define a functor for a set
 instance (Ord a, Ord b) = Functor' S.Set a b where
    fmap' = S.map


 -- Define a degenerate functor, for an integer
 newtype I a = I Integer deriving Show

 instance Functor'  I Integer Integer where
    fmap' f (I x) = I $ f x

 -- tests

 -- Lists as functors
 test_l = fmap' (+10) [1,2,3,4]
 -- [11,12,13,14]

 -- Sets as functors
 test_s = fmap' (\x - x `mod` 3) $ S.fromList [1,2,3,4]
 -- fromList [0,1,2]

 -- Integer as functor
 test_i = fmap' (* (6::Integer)) $ I 7
 -- I 42


 ___
 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] monoids and monads

2010-07-27 Thread John Lato
On Tue, Jul 27, 2010 at 8:32 AM, Henning Thielemann
schlepp...@henning-thielemann.de wrote:
 John Lato schrieb:
 Hello,

 I was wondering today, is this generally true?

 instance (Monad m, Monoid a) = Monoid (m a) where
   mempty = return mempty
   mappend = liftM2 mappend

 I know it isn't a good idea to use this instance, but assuming that
 the instance head does what I mean, is it valid?  Or more generally is
 it true for applicative functors as well?  I think it works for a few
 tricky monads, but that's not any sort of proof.  I don't even know
 how to express what would need to be proven here.

 I translate 'valid' and 'true' to Is 'm a' a Monoid, given that 'm' is
 a Monad and 'a' is a Monoid? If this is the question then we have to
 show the Monoid laws for (m a), namely

Thanks very much, this is what I was unable to express properly (hence
the informal description).

 left identity:   forall x. mappend mempty x = x
 right identity:  forall x. mappend x mempty = x
 associativity:
   forall x y z.
      (x `mappend` y) `mappend` z = x `mappend` (y `mappend` z)

So the task now is to prove that these laws hold, given the instance I
defined above, the monoid laws for 'a', and the monad laws for 'm'.
Or alternatively using applicative laws for 'm' for the more general
case.  I'll see how I get on from here then.

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


Re: [Haskell-cafe] monoids and monads

2010-07-27 Thread John Lato
On Mon, Jul 26, 2010 at 5:02 PM, Edward Kmett ekm...@gmail.com wrote:

 On Mon, Jul 26, 2010 at 11:55 AM, John Lato jwl...@gmail.com wrote:

 Hello,

 I was wondering today, is this generally true?

 instance (Monad m, Monoid a) = Monoid (m a) where
  mempty = return mempty
  mappend = liftM2 mappend

 There are multiple potential monoids that you may be interested in here.

 There is the monoid formed by MonadPlus, there is the monoid formed by
 wrapping a monad (or applicative) around a monoid, which usually forms part
 of a right seminearring because of the left-distributive law, there are also
 potentially other monoids for particular monads.

 See the monad module in my monoids package:

 http://hackage.haskell.org/packages/archive/monoids/0.2.0.2/doc/html/Data-Monoid-Monad.html

I think your monoids package has grown since I last looked at it.
I'll take a look.



 Any resources for how I could develop a means to reason about this
 sort of property?

 The types are not enough.

 What you need is the associativity of Kleisli arrow composition and the two
 identity laws.

 The three monad laws are precisely what you need to form this monoid. There
 are analogous laws for Applicative that serve the same purpose.

Thanks very much.  With this and Henning's hints, I think I can make
some progress with this now.

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


Re: [Haskell-cafe] Haskell Forum

2010-07-27 Thread Ketil Malde
Brandon S Allbery KF8NH allb...@ece.cmu.edu writes:

 Usenet *is* NNTP.

In the same way the web is HTTP...

(Usenet is a set of global, distributed forums using a message format
similar enough to email (RFC822 + extensions) that many mail reader
software supports news, and vice versa.  NNTP is the protocol used for
user access and distribution.  IIRC - anybody interested in more
accuracy will have to look it up :-)

-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: Instances for Set of Functor, Traversable?

2010-07-27 Thread Ivan Lazar Miljenovic
o...@okmij.org writes:

 class Functor' f a b where
 fmap' :: (a - b) - f a - f b

I was about to ask why you mentioned b in the type signature as well, as
I thought just having (Functor' f b) as a constraint in the type
signature of fmap' would be sufficient, but when I went to check I found
that I was mistaken.

*sigh* this is going to make some of my code even uglier than it already
 is :(

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


Re: [Haskell-cafe] 1st attempt at concurrency

2010-07-27 Thread Günther Schmidt

Dear Jason,


And yes, Orc is pretty cool and should be perfectly suited for what you're
doing as fetching data from websites was one of the original use cases for
Orc.

Jason



thanks for that, it's nice to be on the right track for once.

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


Re: [Haskell-cafe] Actors and message-passing a la Erlang

2010-07-27 Thread Stefan Schmidt
Hi Yves,


 You say that With the help of this library it is possible to build
 Erlang-Style mailboxes, but how would you solve the issue of static typing?


this wasn't an issue for me because I wanted as much type checking as
possible. In many implementations, you have an implicit contract between the
sender and the receiver process. In this case, the contract is explicit and
the compiler can tell me if I'm trying to send or receive wrong data.



 Besides, Holumbus depends on package 'unix', preventing it from being used
 on non-unix platforms.


Oh... hmm, I think, the unix-package is only needed for the console-modules.
The distribution modules should not need them, but I may be wrong. I don't
have access to proprietary plattforms, but I think about splitting the
distribution package and extract the communication modules.

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


Re: [Haskell-cafe] Haskell Forum

2010-07-27 Thread namekuseijin
On Tue, Jul 27, 2010 at 12:09 AM, aditya siram aditya.si...@gmail.com wrote:
 We have a Google group. Doesn't that qualify?

One can't post to Haskell Cafe through the usenet/NNTP/google group interface...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] monoids and monads

2010-07-27 Thread Henning Thielemann
John Lato schrieb:
 Hello,
 
 I was wondering today, is this generally true?
 
 instance (Monad m, Monoid a) = Monoid (m a) where
   mempty = return mempty
   mappend = liftM2 mappend
 
 I know it isn't a good idea to use this instance, but assuming that
 the instance head does what I mean, is it valid?  Or more generally is
 it true for applicative functors as well?  I think it works for a few
 tricky monads, but that's not any sort of proof.  I don't even know
 how to express what would need to be proven here.

I always assumed that 'm a' would be a monoid for 'm' being an
applicative functor, but I never tried to prove it. Now you made me
performing a proof. However the applicative functor laws from
http://www.haskell.org/ghc/docs/6.12.2/html/libraries/base-4.2.0.1/Control-Applicative.html
are quite unintuitive and the proofs are certainly not very
illustrative. For the proof of the associativy I have just started from
both ends and worked toward where the associativity of 'a' has to be
inserted, added some mistakes and restarted.


Left Identity
-

(mappend mempty x :: m a)
   = liftA2 mappend (pure mempty) x
   = pure mappend * pure mempty * x
   = pure (mappend mempty) * x
   = pure id * x
   = x


Right Identity
--

(mappend x mempty :: m a)
   = liftA2 mappend x (pure mempty)
   = (pure mappend * x) * pure mempty
   = pure ($mempty) * (pure mappend * x)
   = pure (.) * pure ($mempty) * pure mappend * x
   = pure ((.) ($mempty)) * pure mappend * x
   = pure (($mempty).) * pure mappend * x
   = pure ((($mempty).) mappend) * x
   = pure (($mempty) . mappend) * x
   = pure (\a - ($mempty) (mappend a)) * x
   = pure (\a - (mappend a) mempty) * x
   = pure (\a - a) * x
   = pure id * x
   = x


For monads I find the proof more intuitive:
liftM2 mappend x (pure mempty)
   = do y - x
z - pure mempty
return (mappend y z)
   = do y - x
return (mappend y mempty)
   = do y - x
return y
   = x


Associativity
-

((x `mappend` y) `mappend` z) :: m a
   = (pure mappend * x * y) `mappend` z
   = pure mappend * (pure mappend * x * y) * z
   = pure (.) * pure mappend * (pure mappend * x) * y * z
   = pure (mappend.) * (pure mappend * x) * y * z
   = pure (.) * pure (mappend.) * pure mappend * x * y * z
   = pure ((mappend.).) * pure mappend * x * y * z
   = pure ((mappend.) . mappend) * x * y * z

   -- see proof below

   = pure (($mappend).((.).((.).mappend))) * x * y * z
   = pure (.) * pure ($mappend) * pure ((.).((.).mappend)) * x *
y * z
   = pure ($mappend) * (pure ((.).((.).mappend)) * x) * y * z
   = pure ((.).((.).mappend)) * x * pure mappend * y * z
   = pure (.) * pure (.) * pure ((.).mappend) * x * pure mappend
* y * z
   = pure (.) * (pure ((.).mappend) * x) * pure mappend * y * z
   = pure ((.).mappend) * x * (pure mappend * y) * z
   = pure (.) * pure (.) * pure mappend * x * (pure mappend *
y) * z
   = pure (.) * (pure mappend * x) * (pure mappend * y) * z
   = (pure mappend * x) * ((pure mappend * y) * z)
   = pure mappend * x * (pure mappend * y * z)
   = x `mappend` (pure mappend * y * z)
   = x `mappend` (y `mappend` z)


((mappend.) . mappend) x y z
   = (mappend.) (mappend x) y z
   = (\f - mappend.f) (mappend x) y z
   = (\f x - mappend (f x)) (mappend x) y z
   = mappend (mappend x y) z
   -- Monoid associativity for type 'a'
   = mappend x (mappend y z)
   = (.) (mappend x) (mappend y) z
   = ((.).mappend) x (mappend y) z
   = (.) (((.).mappend) x) mappend y z
   = ((.).((.).mappend)) x mappend y z
   = ($mappend) (((.).((.).mappend)) x) y z
   = (($mappend).((.).((.).mappend))) x y z

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


Re: [Haskell-cafe] Actors and message-passing a la Erlang

2010-07-27 Thread David Leimbach
On Tue, Jul 27, 2010 at 5:27 AM, Stefan Schmidt 
stefanschmid...@googlemail.com wrote:

 Hi Yves,


 You say that With the help of this library it is possible to build
 Erlang-Style mailboxes, but how would you solve the issue of static typing?


 this wasn't an issue for me because I wanted as much type checking as
 possible. In many implementations, you have an implicit contract between the
 sender and the receiver process. In this case, the contract is explicit and
 the compiler can tell me if I'm trying to send or receive wrong data.



I've found that I like Erlang's pattern matching for sorting through
different kinds of data payloads, but that I prefer to use typed data
channels per Limbo, Go, Plan 9's thread and messaging libraries etc.  I've
often wanted an Erlang with static typing to get this capability.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Actors and message-passing a la Erlang

2010-07-27 Thread Joseph Wayne Norton


This may not be of direct interest to the Haskell community but I thought  
I'd share this information anyway.


If you are looking for a solution (in Erlang that runs on Erlang's virtual  
machine) to enforce an explicit contract between a client and a server,  
there is framework called UBF.  This framework is designed for providing  
rpc-like services based on a contract.  The contract is enforced  
dynamically at runtime (not at compile time).


The original implementation was made by Joe Armstrong  
(http://www.sics.se/~joe/ubf/site/home.html).  An updated implementation  
with new features is currently hosted on GitHub (www.github.com/norton).


thanks,

- Joe N.

On Tue, 27 Jul 2010 22:13:07 +0900, David Leimbach leim...@gmail.com  
wrote:



On Tue, Jul 27, 2010 at 5:27 AM, Stefan Schmidt 
stefanschmid...@googlemail.com wrote:


Hi Yves,



You say that With the help of this library it is possible to build
Erlang-Style mailboxes, but how would you solve the issue of static  
typing?




this wasn't an issue for me because I wanted as much type checking as
possible. In many implementations, you have an implicit contract  
between the
sender and the receiver process. In this case, the contract is explicit  
and

the compiler can tell me if I'm trying to send or receive wrong data.




I've found that I like Erlang's pattern matching for sorting through
different kinds of data payloads, but that I prefer to use typed data
channels per Limbo, Go, Plan 9's thread and messaging libraries etc.   
I've

often wanted an Erlang with static typing to get this capability.



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


Re: [Haskell-cafe] monoids and monads

2010-07-27 Thread Dan Doel
On Tuesday 27 July 2010 8:50:56 am Henning Thielemann wrote:
 I always assumed that 'm a' would be a monoid for 'm' being an
 applicative functor, but I never tried to prove it. Now you made me
 performing a proof. However the applicative functor laws from
 http://www.haskell.org/ghc/docs/6.12.2/html/libraries/base-4.2.0.1/Control-
 Applicative.html are quite unintuitive and the proofs are certainly not
 very illustrative.

Perhaps a clearer approach is to look at the category theory behind this.

First, a monoid object in a monoidal category (C, I, ⊗) consists of

  An object M
  e : I - M
  m : M ⊗ M - M

satisfying unit and associativity diagrams. Second, a lax monoidal functor F 
between two monoidal categories C and D gets you:

  unit : I_D - F I_C
  pair : FA ⊗_D FB - F(A ⊗_C B)

also satisfying unit and associativity diagrams. We're only dealing with 
endofunctors, so the above simplifies to:

  unit : I - F I
  pair : forall A B. F A ⊗ F B - F(A ⊗ B)

and in the Haskell case, you get applicative functors via:

  pure x  = fmap (const x) unit
  f * x = fmap (uncurry ($)) (pair (f, x))

So, if we have a monoid object M and monoidal functor F, then we have:

  Fe . unit : I - FM
  Fm . pair : FM ⊗ FM - FM

which should be suggestive. From there, the unit and associativity laws for FM 
as a monoid object should follow pretty naturally using laws of the parts. For 
instance...

  I ⊗ FM - FI ⊗ FM - FM ⊗ FM - F(M ⊗ M) - FM
is the same as
  I ⊗ FM - FM via the isomorphism for the monoidal category


 1) We know that
  I ⊗ FM - FI ⊗ FM - F(I ⊗ M) - FM
is the same as
  I ⊗ FM - FM
from F's left-identity coherence law

 2) We know that
  I ⊗ M - M ⊗ M - M
is the same as
  I ⊗ M - M
from M's left-identity law, and thus
  F(I ⊗ M) - F(M ⊗ M) - FM
is the same as
  F(I ⊗ M) - FM
from F being a functor.

 3) Finally, we know that
  FI ⊗ FM - FM ⊗ FM - F(M ⊗ M)
is the same as
  FI ⊗ FM - F(I ⊗ M) - F(M ⊗ M)
because 'pair' is supposed to be natural in A and B.

 So:

   I ⊗ FM - FM
 is the same as (1)
   I ⊗ FM - FI ⊗ FM - [F(I ⊗ M) - FM]
 is the same as (2)
   I ⊗ FM - [FI ⊗ FM - F(I ⊗ M) - F(M ⊗ M)] - FM
 is the same as (3)
   I ⊗ FM - FI ⊗ FM - FM ⊗ FM - F(M ⊗ M) - FM

 which is left-identity.

Right-identity is exactly the same proof with objects reflected around the ⊗. 
Associativity of the monoid should be a similar application of the 
associativity laws, plus functor and naturality identities.

You could also couch these in terms of Haskell if preferred:

  unit :: f ()
  pair :: (f a, f b) - f (a, b)
  assoc (x, (y, z)) = ((x, y), z)

  fmap (f *** g) . pair = pair . (fmap f *** fmap g)
  fmap assoc . pair . (id *** pair) = pair . (pair *** id) . assoc
  etc.

Alternately, if you accept authority:

  Lax monoidal functors send monoids to monoids
http://ncatlab.org/nlab/show/monoidal+functor

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


Re: [Haskell-cafe] Is 'flip' really necessary?

2010-07-27 Thread wren ng thornton

aditya siram wrote:

Eta-reducing is nice, and sometimes it makes code more readable. But 'flip'
is one of those functions that always seems to hinder rather than help
readability, conversely factoring out flip always makes code easier to
comprehend. I don't see a need for its existence - maybe I'm missing
something and more experienced Haskellers can comment.


Not quite Haskell but, in combinator calculi 'flip' is unexpectedly 
powerful. It'd be odd not to have/use it in Haskell. Though in general I 
agree that it should be used sparingly, for legibility's sake.


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


Re: [Haskell-cafe] Re: Lists and monads

2010-07-27 Thread wren ng thornton

Kevin Jardine wrote:

But as I said, that is just an example. I keep wanting to apply the
usual list tools but find that they do not work inside a monad. I find
myself wishing that f (m [a]) just automatically returned m f([a])


Are you looking for these?

import Data.Traversable as T
T.sequence :: (T.Traversable t, Monad m) = t (m a) - m (t a)
T.mapM :: (T.Traversable t, Monad m) = (a - m b) - t a - m (t b)
-- N.B. T.mapM ~ (T.sequence . fmap)


without me needing to do anything but I expect that there are reasons
why that is not a good idea.


Not all functors can be distributed over arbitrary monads, so not a 
good idea is more like not always possible or here be dragons 
(fluffy, intriguing, and pretty dragons to be sure; but probably deeper 
than the answer you were looking for).


In addition to Applicative, the Traversable and Foldable classes should 
be key tools in your toolbox. They take a number of functions typically 
restricted to lists and generalize them to different functors, often 
with Applicatives or Monads involved. The Typeclassopedia should have 
more on them.


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


Re: [Haskell-cafe] monoids and monads

2010-07-27 Thread wren ng thornton

Henning Thielemann wrote:

However the applicative functor laws from
http://www.haskell.org/ghc/docs/6.12.2/html/libraries/base-4.2.0.1/Control-Applicative.html
are quite unintuitive and the proofs are certainly not very
illustrative.


I always found it more illustrative to break it down and talk about 
pointed functors, where 'return' is trivial in 'fmap' (forgive the Coq 
syntax):


 fmap_pointed
: forall {A B : Type} (f : A - B) (a : A)
, f $ return a = return $ f a

And then you only need three laws, the obvious ones:

app_return_left
: forall {A B : Type} (f : A - B) (xa : F A)
, return f * xa = f $ xa

app_return_right
: forall {A B : Type} (xf : F (A - B)) (a : A)
, xf * return a = ($a) $ xf

app_compose
: forall {A B C : Type}
, forall (xf : F (B - C)) (xg : F (A - B)) (xa : F A)
, compose $ xf * xg * xa = xf * (xg * xa)

That is, we have that 'return' is (in the appropriate sense) the left 
and right identity for (*), which allows us to apply fmap_pointed to 
reduce (*) into ($). Since only one of the arguments has a 
non-trivial structure, that's the structure we use for ($).


And then we have (again in the appropriate sense) associativity of 
composition. Which is really just to say that composition from the pure 
world is preserved as composition in the applicative world.


The other two laws (app_identity : ..., return id $ xa = xa) and 
(app_homomorphism : ..., return f * return a = return (f a)) follow 
directly from fmap_pointed. Or conversely, given these five laws we can 
always prove fmap_pointed.


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


Re: [Haskell-cafe] An experimental Zipper using Thrists and first-class Labels. Help or thoughts?

2010-07-27 Thread Brandon Simmons
On Tue, Jul 27, 2010 at 1:59 AM, Jason Dagit da...@codersbase.com wrote:


 On Mon, Jul 26, 2010 at 9:00 PM, Brandon Simmons
 brandon.m.simm...@gmail.com wrote:

 I had the idea for a simple generic Zipper data structure that I
 thought would be possible to implement using type-threaded lists
 provided by Gabor Greif's thrist package:

    http://hackage.haskell.org/package/thrist

 ...and the fclabels package by Sebastiaan Visser, Erik Hesselink,
 Chris Eidhof and Sjoerd Visscher:

    http://hackage.haskell.org/package/fclabels

 It would (ideally) work as follows:

 - the zipper would consist simply of a tuple:
       (type threaded list of constructor sections , current context)
 - in the type threaded list we store functions (constructor with hole
 - complete constructor), so the
    one hole context is represented as a lambda expression where the
 free variable will be filled
    by the current context (the snd of the tuple)
 - we go down through our structure by passing to our `moveTo`
 function a first-class label
    corresponding to the constructor we want to descend into. `moveTo`
 uses this both as a getter
    to extract the next level down from the current level, and as a
 setter to form the lambda expression
    which acts as the constructor with a piece missing
 - going up means popping the head off the thrist and applying it to
 the current context, making that
    the new context, exiting the zipper would be a fold in the same manner


 After throwing together a quick attempt I realized that I'm not sure
 if it would be possible to make the `moveUp` function type-check and
 be usable. I'm still new to GADTs, existential types, template haskell
 etc. and am stuck.

 Here is the code I wrote up, which doesn't currently compile:


 --  START CODE
 ---

 {-# LANGUAGE TypeOperators, GADTs #-}
 module ZipperGenerator
    (
      viewC   --lets user pattern match against context
    , moveTo
    , moveUp
    , genZippers
    , zipper
    , unzipper
    , (:-)
    , ZipperGenerator
    , Zipper
    ) where

 -- these provide the secret sauce
 import Data.Record.Label
 import Data.Thrist
 import Language.Haskell.TH


 type ZipperGenerator = [Name] - Q [Dec]

 -- the Template Haskell function that does the work of generating
 -- first-class labels used to move about the zipper:
 genZippers :: ZipperGenerator
 genZippers = mkLabels

 -- hide the innards:
 newtype Zipper t c = Z (Thrist (-) c t, c)

 -- returns the current context (our location in the zipper) for pattern
 -- matching and inspection:
 viewC :: Zipper t c - c
 viewC (Z(_,c)) = c

 -- takes a first-class label corresponding to the record in the current
 context
 -- that we would like to move to:
 moveTo :: (c :- c') - Zipper t c - Zipper t c'
 moveTo lb (Z(thr,c)) = Z (Cons (\a- set lb a c) thr , get lb c)


 -- backs up a level in the zipper, returning `Nothing` if we are already
 at the
 -- top level:
 moveUp :: Zipper t c - Maybe (Zipper t b)
 moveUp (Z (Nil,_)) = Nothing
 moveUp (Z (Cons f thr,c)) = Just $ Z (thr, f c)

 -- create zipper with focus on topmost constructor level:
 zipper :: t - Zipper t t
 zipper t = Z (Nil,t)

 -- close zipper
 unzipper :: Zipper t c - t
 unzipper (Z(thr,c)) = undefined --foldThrist ($) id thr c

 Hmm...I think you just need to change ($) to (.).  I haven't tested it.
  But, if you have Thrist (-) c t, then what you have is a transformation
 from c to t, or more simply, c - t.  So, conceptually at least, you just
 need to compose the elements in your Thrist.  ($) is application, but in the
 space of functions it is identity.  So, if you think the elements in your
 thrist as being values in the space of functions, you're asking for a right
 fold that is like, v1 `id` (v2 `id` (v3 `id` ...), which I hope you agree
 doesn't make that much sense.  So try this:
 unzipper (Z(thr,c)) = foldThrist (.) id thr c
 In the darcs source we use our own custom thrists for storing sequences of
 patches.  We have two variants, forward lists (FL) and reverse lists (RL).
  In our parlance, we have foldlFL defined thusly:
 foldlFL :: (forall w y. a - b w y - a) - a - FL b x z - a
 foldlFL _ x NilFL = x
 foldlFL f x (y::ys) = foldlFL f (f x y) ys
 We don't use Control.Arrow, so in our notation the 'b' in the type signature
 plays the same role as (~) but in prefix notation, of course.  And we use
 (::) instead of Cons.  It's supposed to look like normal list cons but with
 an arrow pointing forward.  The cons for RL is (::).  Perhaps we should use
 arrow though, as I think that looks pretty nice.
 For comparison, here is the definition of foldThrist:
 foldThrist :: (forall i j k . (i ~ j) - (j ~ k) - (i ~ k))
 - c ~ c
 - Thrist (~) a c
 - a ~ c
 foldThrist _ v Nil = v
 foldThrist f v (Cons h t) = h `f` (foldThrist f v t)
 As you can see, our fold is a left fold and the thrist fold is a right fold.
  I don't think a left fold will help you here, but you might 

Re: [Haskell-cafe] Haskell Forum

2010-07-27 Thread Andrew Coppin

Magnus Therning wrote:

On 26/07/10 22:01, Andrew Coppin wrote:
  

So I'm told. But it appears that some people believe that NNTP *is*
Usenet, which is not the case. I use NNTP almost every single day, but
I've never seen Usenet in my life...



So you've only ever been on private NNTP servers then, never browsed through
comp.* or sci.*?
  


I don't even know what they are. (Except that now, by inference, I can 
guess they're something to do with Usenet.)


For example, Microsoft has a private NNTP server for technical support.

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


Re: [Haskell-cafe] Re: Haskell Forum

2010-07-27 Thread Andrew Coppin

John Meacham wrote:

There already is an NNTP - mailing list gateway via gmane that gives a
nice forumy and threaded web interface for those with insufficient email
readers. Adding a completely different interface seems unnecessary and
fragmentary.
  


Trouble is, you can't use it like just another NNTP server.

If you have a forum powered by NNTP, you can casually throw in a hey, 
nice one time comment as a reply to part of a thread, and only people 
interested in that thread have to see your message (or download it, for 
that matter). If you do that on a mailing list, all 700+ subscribers get 
a copy of your email. And, usually, they're not very amused about it. 
With SMTP, you can only really say something if it's really, really 
worth saying. Otherwise it just gets too noisy. That's the trouble with 
a mailing list; it's everyone talking to everyone. NNTP has real 
threading, and a central place where all the messages can be 
redownloaded from incrimentally, and it doesn't get eaten by your ISP's 
spam filter, and and and...


Still, I know from experience that I am the only person here who 
appreciates these virtues. Everybody else seems quite happy with a crude 
SMTP system, so...


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


[Haskell-cafe] Int and ByteStrings

2010-07-27 Thread wren ng thornton

Hey all,

Is there a library function (f :: [Int] - ByteString) such that it's 
prefix-preserving, and platform independent? GHC-only is fine for now. 
There are a bunch of functions of that type, but I need those guarantees 
and I'm hoping someone else has already done it.


If there isn't one for Int, has someone already made a package that 
offers IntMap on Word32, Word64, etc?


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


Re: [Haskell-cafe] Re: Haskell Forum

2010-07-27 Thread Mihai Maruseac
From my experience once a forum pops up the mailing list dies.

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


Re: [Haskell-cafe] Actors and message-passing a la Erlang

2010-07-27 Thread Yves Parès
I've found that I like Erlang's pattern matching for sorting through
different kinds of data payloads, but that I prefer to use typed data
channels per Limbo, Go, Plan 9's thread and messaging libraries etc.  I've
often wanted an Erlang with static typing to get this capability.

Actually you are right. And it is not much of a chore to write:
data MyMessages = Something XXX | SomethingElse YYY ZZZ | Stop | ...
given that it ensures your message-passing is correct at compile time.

It gives you an Actor type like:
data Actor msgIn msgOut
Where msgIn is the type of received messages (Erlang's 'receive') and msgOut
the type of sent messages (Erlang's '!').


2010/7/27 David Leimbach leim...@gmail.com



 On Tue, Jul 27, 2010 at 5:27 AM, Stefan Schmidt 
 stefanschmid...@googlemail.com wrote:

 Hi Yves,


 You say that With the help of this library it is possible to build
 Erlang-Style mailboxes, but how would you solve the issue of static typing?


 this wasn't an issue for me because I wanted as much type checking as
 possible. In many implementations, you have an implicit contract between the
 sender and the receiver process. In this case, the contract is explicit and
 the compiler can tell me if I'm trying to send or receive wrong data.



 I've found that I like Erlang's pattern matching for sorting through
 different kinds of data payloads, but that I prefer to use typed data
 channels per Limbo, Go, Plan 9's thread and messaging libraries etc.  I've
 often wanted an Erlang with static typing to get this capability.



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


[Haskell-cafe] Re: Lists and monads

2010-07-27 Thread Kevin Jardine
Looks interesting.

I've also come across Data.List.Class:

http://hackage.haskell.org/packages/archive/generator/0.5.1/doc/html/Data-List-Class.html

Has anyone used that?

Kevin

On Jul 27, 6:02 pm, wren ng thornton w...@freegeek.org wrote:
 Kevin Jardine wrote:
  But as I said, that is just an example. I keep wanting to apply the
  usual list tools but find that they do not work inside a monad. I find
  myself wishing that f (m [a]) just automatically returned m f([a])

 Are you looking for these?

      import Data.Traversable as T
      T.sequence :: (T.Traversable t, Monad m) = t (m a) - m (t a)
      T.mapM :: (T.Traversable t, Monad m) = (a - m b) - t a - m (t b)
      -- N.B. T.mapM ~ (T.sequence . fmap)

  without me needing to do anything but I expect that there are reasons
  why that is not a good idea.

 Not all functors can be distributed over arbitrary monads, so not a
 good idea is more like not always possible or here be dragons
 (fluffy, intriguing, and pretty dragons to be sure; but probably deeper
 than the answer you were looking for).

 In addition to Applicative, the Traversable and Foldable classes should
 be key tools in your toolbox. They take a number of functions typically
 restricted to lists and generalize them to different functors, often
 with Applicatives or Monads involved. The Typeclassopedia should have
 more on them.

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


Re: [Haskell-cafe] Re: Haskell Forum

2010-07-27 Thread Darrin Chandler
On Tue, Jul 27, 2010 at 07:01:45PM +0100, Andrew Coppin wrote:
 If you have a forum powered by NNTP, you can casually throw in a
 hey, nice one time comment as a reply to part of a thread, and
 only people interested in that thread have to see your message (or
 download it, for that matter).
...

 Still, I know from experience that I am the only person here who
 appreciates these virtues. Everybody else seems quite happy with a
 crude SMTP system, so...

IOW, if people use the proper and well known features of NNTP it would
be a better world than the one we have were people do not use proper and
well known features of SMTP.

As it stands, even with SMTP you get people who post new message topics
as replies to existing threads, as well as people who *somehow* reply
to a thread but do not include In-Reply-To or References headers so
threading is broken. I have no reason to think people would not do the
same broken things with NNTP, foiling my plans for following some
threads and ignoring others.

As long as people are sharing opinions, I'll add mine:

* If the mailing lists go away I will probably not switch to whatever
  replaces it.
* A list - forum gateway is fine, as long as the message IQ doesn't
  drop through the floor as a result. This fear comes from personal,
  anecdotal evidence. YMMV.
* No opinion either way on List - NNTP gateway.

-- 
Darrin Chandler|  Phoenix BSD User Group  |  MetaBUG
dwchand...@stilyagin.com   |  http://phxbug.org/  |  http://metabug.org/
http://www.stilyagin.com/  |  Daemons in the Desert   |  Global BUG Federation
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Int and ByteStrings

2010-07-27 Thread Don Stewart
wren:
 Hey all,

 Is there a library function (f :: [Int] - ByteString) such that it's  
 prefix-preserving, and platform independent? GHC-only is fine for now.  
 There are a bunch of functions of that type, but I need those guarantees  
 and I'm hoping someone else has already done it.

should be possible to write using Data.Binary.

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


Re: [Haskell-cafe] transform function for a GADT

2010-07-27 Thread Ryan Ingram
I'd add another parameter to the ExprType class and give an explicit
representation to your types.

data EType a where
EInt :: EType Int
EBool :: EType Bool

data TypeEq a b where Refl :: TypeEq x x

eqEType :: ExprType a - ExprType b - Maybe (TypeEq a b)
eqEType EInt EInt = Just Refl
eqEType EBool EBool = Just Refl
eqEType _ _ = Nothing

class ExprType a where
toExpr :: a - Expr a
eType :: EType a

eTypeOf :: Expr a - EType a
eTypeOf (Bin _) = EBool
eTypeOf (Num _) = EInt
eTypeOf (_ :+: _) = EInt
-- etc.

transform :: (ExprType a, ExprType b) = (Expr b - Expr b) - Expr a - Expr a
transform = transform' eType

-- uses LANGUAGE PatternGuards
transform' :: EType b - (Expr b - Expr b) - Expr a - Expr a
transform' t f e | Just Refl - eqEType t (eTypeOf e) = f e   -- this
is the magic line
transform' t f (Bin b) = Bin b
tranfsorm' t f (Num i) = Num i
transform' t f (e1 :+: e2) = transform' t f e1 :+: transform' t f e2
-- etc.

The magic line checks if the type of the expression matches the type
of the function, and if so, applies it.

  -- ryan

On Tue, Jul 27, 2010 at 8:28 AM, Ozgur Akgun ozgurak...@gmail.com wrote:
 Café,

 I've tried several things already, but I am not including any of them for
 now.
 My question is, how would you define the 'transform' function for a GADT,
 say the one in the linked gist: http://gist.github.com/492364 (also attached
 to this e-mail)

 To be concise, I want 'transform' to apply the transformation function (its
 first parameter) to every immidiate child of its second parameter as long as
 the types match. Similar to what the 'tranform' function of Uniplate does
 for normal ADTs. (But just one level, so I guess it is more similar to the
 'descend' of Uniplate. See
 http://hackage.haskell.org/packages/archive/uniplate/1.2.0.1/doc/html/Data-Generics-UniplateStr.html)

 I think I got closest to a sensible solution using multi-param type classes,
 and defining many instances for different combinations of ExprType's but
 still there were problems.

 Waiting for suggestions and/or insights.

 Best,
 Ozgur Akgun

 ___
 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] Parsec Best Practices examples

2010-07-27 Thread David Place
Hi, All.

I have a compiler written in Parsec and Haskell for a DSL.  It's quite 
rudimentary since I made it for my own use only.  I would like to make it 
useable by a slightly wider circle.  For this, I need better error reporting.  
Currently, it terminates after finding one syntax error.  I would like to 
detect as many syntax errors as possible and report them before terminating.  
Are there any best practices examples of how to do this available?  It seems 
like something many people would have solved already.

Cheers,
David


David F. Place   
Owner, Panpipes Ho! LLC
http://panpipesho.com
d...@vidplace.com



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


Re: [Haskell-cafe] Re: Haskell Forum

2010-07-27 Thread Andrew Coppin

Darrin Chandler wrote:

IOW, if people use the proper and well known features of NNTP it would
be a better world than the one we have were people do not use proper and
well known features of SMTP.
  


SMTP is designed for delivering messages point-to-point. If your email 
provider incorrectly marks half the list traffic as spam, you can't read 
it. If your PC dies and you lose all your email, you cannot get it back 
again. If you hit reply, it only replies to the one person who wrote the 
message, not to the list. And every person has to download every single 
message ever sent. Because, let's face it, all a list server does is 
receive emails and then re-send them to everybody. If your mail system 
isn't operational at the moment when the email is sent, you'll never 
receive it and cannot ever get it afterwards.


NNTP is designed to deliver list traffic. You can tell your news reader 
to download messages posted before you joined the group (which is 
impossible with a mailing list). If your PC dies, you can just 
re-download all the messages again. Threading actually works properly. 
You only need download the message bodies that you're actually 
interested in. And so on.



As it stands, even with SMTP you get people who post new message topics
as replies to existing threads, as well as people who *somehow* reply
to a thread but do not include In-Reply-To or References headers so
threading is broken. I have no reason to think people would not do the
same broken things with NNTP, foiling my plans for following some
threads and ignoring others.
  


I constantly have trouble with this mailing list. Even gmane can't seem 
to thread it properly. But I've never had any trouble with threading in 
any NNTP group, ever.


[Well, apart from that stupid Thunderbird bug they still haven't fixed 
yet. But that's a client bug. Use a different client and it goes away.]



* If the mailing lists go away I will probably not switch to whatever
  replaces it.
  


...nd this is why no matter how superior it is, this list will never 
get updated.



* A list - forum gateway is fine, as long as the message IQ doesn't
  drop through the floor as a result. This fear comes from personal,
  anecdotal evidence. YMMV.
  


Uh, why would that happen?

I guess if it went to a web forum there'd by a greater danger of that 
maybe. But heck, we don't have much trouble on IRC, and that's notorious 
for the kind of trolls it tends to attract...



* No opinion either way on List - NNTP gateway.
  


As I say, there already is one. But because 98% of everybody uses this 
list as an email list, you can't go using it like it's a news group. 
You'll just get yelled at.


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


Re: [Haskell-cafe] Re: Haskell Forum

2010-07-27 Thread Nick Bowler
On 2010-07-27 19:59 +0100, Andrew Coppin wrote:
 Darrin Chandler wrote:
  IOW, if people use the proper and well known features of NNTP it would
  be a better world than the one we have were people do not use proper and
  well known features of SMTP.
 
 SMTP is designed for delivering messages point-to-point. If your email 
 provider incorrectly marks half the list traffic as spam, you can't read 
 it.

This has nothing to do with SMTP, and everything to do with your email
provider being worthless.

 If your PC dies and you lose all your email, you cannot get it back 
 again.

Assuming you've never heard of list archives or backups, sure.

 If you hit reply, it only replies to the one person who wrote the
 message, not to the list.

Every mail client worth its salt has a 'reply to group' function, which
performs as advertised.  In fact, I can't even name a single one that
does not have this function.

 And every person has to download every single message ever sent.
 Because, let's face it, all a list server does is receive emails and
 then re-send them to everybody.

This point is valid, but not really relevant since the advent of DSL.  A
week's traffic on linux-kernel is about 30 megabytes.  Haskell-cafe is
about 4.

 If your mail system isn't operational at the moment when the email is
 sent, you'll never receive it and cannot ever get it afterwards.

This is not an accurate reflection of reality.

 I constantly have trouble with this mailing list. Even gmane can't seem 
 to thread it properly. But I've never had any trouble with threading in 
 any NNTP group, ever.

Mutt seems to have no trouble threading it properly.  I haven't
encountered an issue with gmane and this list, although admittedly I
don't use it often.

 [Well, apart from that stupid Thunderbird bug they still haven't fixed 
 yet. But that's a client bug. Use a different client and it goes away.]

The same can be said about email threading.

-- 
Nick Bowler, Elliptic Technologies (http://www.elliptictech.com/)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Haskell Forum

2010-07-27 Thread Darrin Chandler
On Tue, Jul 27, 2010 at 07:59:40PM +0100, Andrew Coppin wrote:
 NNTP is 
...

It's all true. I used nntp extensively in the 90s. I never emo-quit, I
just stopped using it over time due to waning ISP support and other
reasons made it more of a pain. I have nothing against nntp as a
protocol, but I have my reasons for no longer using it.

 I constantly have trouble with this mailing list. Even gmane can't
 seem to thread it properly. But I've never had any trouble with
 threading in any NNTP group, ever.

Hmm. I don't see this mailing list as unusual in any way wrt threading,
except that most people here actually *do* reply properly, most of the
time.

 * If the mailing lists go away I will probably not switch to whatever
   replaces it.
 
 ...nd this is why no matter how superior it is, this list will
 never get updated.

Pretty much.

 * A list - forum gateway is fine, as long as the message IQ doesn't
   drop through the floor as a result. This fear comes from personal,
   anecdotal evidence. YMMV.
 
 Uh, why would that happen?
 
 I guess if it went to a web forum there'd by a greater danger of
 that maybe. But heck, we don't have much trouble on IRC, and that's
 notorious for the kind of trolls it tends to attract...

In my experience, either a web forum is actively maintained and
moderated or it becomes a troll magnet. Trolls can live anywhere, but
they prefer caves, under bridges, and web forums. People on this list
who desire a forum are not the problem, and I certainly don't want to
imply that.

As for IRC, I think freenode/#haskell has enough quality and quantity to
keep the trolls down. I haven't had much troll problems on freenode,
though I'm sure others could share some tales.

 * No opinion either way on List - NNTP gateway.
 
 As I say, there already is one. But because 98% of everybody uses
 this list as an email list, you can't go using it like it's a news
 group. You'll just get yelled at.

I find it surprising that you'd get yelled at, but I don't really know.

-- 
Darrin Chandler|  Phoenix BSD User Group  |  MetaBUG
dwchand...@stilyagin.com   |  http://phxbug.org/  |  http://metabug.org/
http://www.stilyagin.com/  |  Daemons in the Desert   |  Global BUG Federation
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell at CERN

2010-07-27 Thread Alexey Khudyakov
Hello

I'm wondering is there any haskellers in CERN? Given quality
and usability of software there must be people looking for
better alternatives.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] fine control of bytestring streaming

2010-07-27 Thread Alberto G. Corona
Hi,

I´m streaming content using lazy bytestrings in a web application. The
problem is that the output comes in huge blobs  (presumably of 32k)
one at a time. This is good for some purposes, but not for
console-like interfaces or runtime log visualization. (one of my
purposes is to web-alize ghci. I know that this can be done without
streaming the standard output, but I want it that way).

I can not  control when the IO bytestring primitives flush the data to
the stream, because this is not part of my application (nor does it
should do it).

 I suppose here that it is in a chunk by chunk basis. But maybe I
misinterpreted something or everything. I use the package hack with
the server  hack-handler-simpleserver. this serves does
Data.ByteString.hPut   the bytestring content...

I use mappend to add content to the stream.  mappend uses append
which uses. foldrChunks which  seems not to compact two bytestrings
in  max size chunks . So I do not know what happens.

The question is:  are there some way to control bytestring streaming?.
 Can It be done without the stream handler?






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


Re: [Haskell-cafe] fine control of bytestring streaming

2010-07-27 Thread Henning Thielemann


On Tue, 27 Jul 2010, Alberto G. Corona wrote:


The question is:  are there some way to control bytestring streaming?.
Can It be done without the stream handler?


I think there is a function that converts a lazy ByteString to a list of 
strict ByteStrings, that should work without copying the chunk data 
around. On this chunk list you can do all kind of manipulations, like 
merging adjacent small chunks.

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


Re: [Haskell-cafe] new Cabal user question -- installing to Haskell Platform on Windows network drive?

2010-07-27 Thread Peter Schmitz
Rogan:

Thanks very much.

I began by downloading the latest gtk+ bundle from
http://www.gtk.org/download-windows.html

The instructions there said to just copy the files to any dir and add its
...\gtk\bin dir to my PATH, which I did, so that worked okay without admin
privs.

Given that I need to use these tools on a network drive (H:), and not C:,
I have installed the Platform and gtk to:
H:\proc\tools\Haskell Platform and
H:\proc\tools\gtk

(My H: is a hdd, not usb; and I am trying to do all this without admin
privs, which is working fine so far.)

The gtk tests: pkg-config --cflags gtk+-2.0 and gtk-demo run fine. Great!



 Anyone: 

So, I am trying to use cabal (for the first time), on a Windows XP
system/network.

I need to keep everything on H:, and not use C:.

The only copy of cabal I have is what came with the Platform:
H:\proc\tools\Haskell Platform\2010.1.0.0\lib\extralibs\bin\cabal.exe.

I placed that bin dir in my PATH and tried a cabal update.

(Does is matter what my current dir is, when I use cabal?)

It said:
H:\proc\dev\cmdcabal update
Config file path source is default config file.
Config file C:\Documents and Settings\pschmitz\Application Data\cabal\config

not found.
Writing default configuration to C:\Documents and
Settings\pschmitz\Application Data\cabal\config
Downloading the latest package list from hackage.haskell.org
Note: there is a new version of cabal-install available.
To upgrade, run: cabal install cabal-install

So, by default, cabal wants to put its config and updates on C:.

I looked at C:\Documents and Settings\pschmitz\Application Data\cabal\config

It has various references to C:, some commented out. E.g.:

remote-repo-cache: C:\Documents and Settings\pschmitz\Application
Data\cabal\packages

build-summary: C:\Documents and Settings\pschmitz\Application
Data\cabal\logs\build.log

install-dirs user
-- prefix: C:\\Documents and Settings\\pschmitz\\Application Data\\cabal

etc.

I also reviewed the Cabal User's Guide, including section
4.1.2.2 Paths in the simple build system
which has a table with command line switches and pathname defaults for
Windows including:
--prefix (global installs with the --global flag)
C:\ProgramFiles\Haskell
and
--prefix (per-user installs with the --user flag)
C:\DocumentsAndSettings\user\ApplicationData\cabal

Given that I want to keep everything on H:,
and assuming that I don't want to place the Cabal configs and updates in the
Platform tree (H:\proc\tools\Haskell Platform),
I would _like_ to create a dir such as
H:\proc\tools\cabal
to hold everything that Cabal would normally put on C:.

*** I'm afraid I'm having trouble figuring out how to accomplish this.

Is there (hopefully) a combination of cabal command line switches that will
create a new config file over on H: for me,
or must I edit the config file directly and move it to H:?

And then, how do I invoke cabal each time, to get it to use its tree on H:
(and ignore C:) ?

Thanks (very much) in advance.
-- Peter Schmitz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Error Monad and strings

2010-07-27 Thread Gerald Gutierrez
Reading the Control.Monad.Error documentation, I see that the Error class
has noMsg and strMsg as its only two functions.

Now, I understand that you can define your own Error instances such as in
example 1 of the documentation, so why the need to always support strings
via noMsg/strMsg ? What uses these? And if in my code, I will never throw an
error with a string, am I supposed to implement these functions and then
ignore them?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Error Monad and strings

2010-07-27 Thread Gregory Crosswhite
It is for the very annoying reason that in order for Error to be a monad
it has to implement the fail method, which means it has to know how to
turn an arbitrary string into a value of your error type.

Cheers,
Greg

On 07/27/10 15:32, Gerald Gutierrez wrote:

 Reading the Control.Monad.Error documentation, I see that the Error
 class has noMsg and strMsg as its only two functions.

 Now, I understand that you can define your own Error instances such as
 in example 1 of the documentation, so why the need to always support
 strings via noMsg/strMsg ? What uses these? And if in my code, I will
 never throw an error with a string, am I supposed to implement these
 functions and then ignore them?


 ___
 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] Error Monad and strings

2010-07-27 Thread Dietrich Epp
The strMsg method is used to implement the fail method in the  
resulting method, and calls to fail might be inserted into your code  
even if you don't explicitly call it.  An example in GHCi:


Prelude :m + Control.Monad.Error
Prelude Control.Monad.Error do { Just x - return Nothing ; return  
x } :: Either String Int

Left Pattern match failure in do expression at interactive:1:5-8

Note that in the Either String monad, failStr is equal to Left.

On 2010 July 27, at 15:32, Gerald Gutierrez wrote:



Reading the Control.Monad.Error documentation, I see that the Error  
class has noMsg and strMsg as its only two functions.


Now, I understand that you can define your own Error instances such  
as in example 1 of the documentation, so why the need to always  
support strings via noMsg/strMsg ? What uses these? And if in my  
code, I will never throw an error with a string, am I supposed to  
implement these functions and then ignore them?


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


Re: [Haskell-cafe] Error Monad and strings

2010-07-27 Thread Gerald Gutierrez
On Tue, Jul 27, 2010 at 3:57 PM, Dietrich Epp d...@zdome.net wrote:

 The strMsg method is used to implement the fail method in the resulting
 method, and calls to fail might be inserted into your code even if you
 don't explicitly call it.  An example in GHCi:
 Prelude :m + Control.Monad.Error
 Prelude Control.Monad.Error do { Just x - return Nothing ; return x } ::
 Either String Int
 Left Pattern match failure in do expression at interactive:1:5-8

 On 2010 July 27, at 15:32, Gerald Gutierrez wrote:

 Reading the Control.Monad.Error documentation, I see that the Error class
 has noMsg and strMsg as its only two functions.
 Now, I understand that you can define your own Error instances such as in
 example 1 of the documentation, so why the need to always support strings
 via noMsg/strMsg ? What uses these? And if in my code, I will never throw an
 error with a string, am I supposed to implement these functions and then
 ignore them?


I see. So strings must be supported in the case of a bug which cannot be
caught at compile time? In other words, if I get an error with a string, I'm
pretty much guaranteed it is a bug, i.e. a pattern match error as the fail
documentation says.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Error Monad and strings

2010-07-27 Thread Dietrich Epp
I'll say yes, a pattern match failure is a bug.  This is one of the  
great debates in the language: whether all pattern matching code  
should be guaranteed complete at compile time or not.  However, any  
function you call which returns a result in your monad could  
theoretically call fail if it was written that way.  Data.Map.lookup  
used to call fail when it could not find a key, but that got changed.


If you don't want to catch these errors in your monad, you can write  
your own monad (or monad transformer).  For example:


newtype ErrorCode = ErrorCode Int deriving Show
newtype ErrorCodeT m a = ErrorCodeT { runErrorCodeT :: m (Either  
ErrorCode a) }

instance Monad m = Monad (ErrorCodeT m) where
return = ErrorCodeT . return . Right
a = b = ErrorCodeT $ do
m - runErrorCodeT a
case m of
Left err - return $ Left err
Right x - runErrorCodeT $ b x
fail = ErrorCodeT . fail
failWithCode :: Monad m = Int - ErrorCodeT m a
failWithCode = ErrorCodeT . return . Left . ErrorCode

There's probabaly a library somewhere which does this already.

On 2010 July 27, at 16:08, Gerald Gutierrez wrote:

I see. So strings must be supported in the case of a bug which  
cannot be caught at compile time? In other words, if I get an error  
with a string, I'm pretty much guaranteed it is a bug, i.e. a  
pattern match error as the fail documentation says.


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


[Haskell-cafe] Re: Haskell Forum

2010-07-27 Thread Benjamin L. Russell
Kevin Jardine kevinjard...@gmail.com writes:

 On Jul 26, 6:45 pm, Nick Bowler nbow...@elliptictech.com wrote:

 Since when do mailing lists not have threading?  Web forums with proper
 support for threading seem to be few and far apart.

 Most of the email clients I'm familiar with don't support threaded
 displays and most of the web forums I'm familiar with do (although the
 feature is not always switched on).

 In my experience the debate between mailing list vs. web forum can
 become very emotional (especially when discussed via a mailing list)
 and I don't think it is that productive. Some people like one, some
 people like the other. That's why I think that it is useful to give
 people a choice.

One problem with creating a Web forum for a topic supported by a
community that already chiefly communicates via a mailing list is that
cross-referencing/cross-posting can become difficult.

Suppose that somebody addresses a topic that has already been introduced
on the mailing list on the forum, and that someone on mailing list then
sees this topic and wants to respond.  Should he/she respond on the
mailing list, or the forum?  How about follow-ups?  What if he/she
wishes to restrict follow-ups to either the forum or the mailing list?

Conversely, suppose that somebody addresses a topic that has already
been introduced on the forum on the mailing list, and that someone on
the forum then sees this topic and wants to respond.  What then?  What
happens if the forum users see some of the content as appropriate for
the mailing list, but not for the forum?

The only viable solution is to have every mailing list post forwarded to
the forum and vice-versa, and have a moderator for the forum filter out
posts containing content that is deemed inappropriate for the Web.  But
then this leads to an additional problem:  What if some users on the
mailing list deem content that has been filtered out by the moderator as
appropriate for discussion on both forums, while the forum users
consider it as inappropriate it?

Consider the following sample discussion (which I just wrote for the
purpose of this discussion, but which actually discusses a possible
topic), which contains issues of technical terms containing scatological
(i.e., dirty) language, multiple levels of indentation, representation
of URLs, and article length (please ignore this example if you feel
upset by technical terms that contain scatological terms):

 subject:  A Comparison of Whitespace in Haskell and brainfuck
 
 I discovered an article (see http://en.wikipedia.org/wiki/Brainfuck)
 on the brainfuck programming language (not to be confused with the
 Brain Fuck Scheduler (BFS) (see
 http://en.wikipedia.org/wiki/Brain_Fuck_Scheduler)) that introduced a
 sample Hello World! program:
 
  The following program prints Hello World! and a newline to the screen:
  
  + + initialize counter (cell #0) to 10
  [   use loop to set the next four cells to 70/100/30/10
   + ++  add  7 to cell #1
   + +   add 10 to cell #2 
   +++   add  3 to cell #3
   + add  1 to cell #4
   -  decrement counter (cell #0)
  ]   
   ++ .  print 'H'
   + .   print 'e'
  + ++ .  print 'l'
  .   print 'l'
  +++ .   print 'o'
   ++ .  print ' '
   + + + .  print 'W'
   . print 'o'
  +++ .   print 'r'
  - - .   print 'l'
  - --- . print 'd'
   + .   print '!'
   . print '\n'
  
  For readability, this code has been spread across many lines and
  blanks and comments have been added. Brainfuck ignores all characters
  except the eight commands +-[],. so no special syntax for comments
  is needed. The code could just as well have been written as: 
  
  ++[+-]++.+.+++..+++.++.+++..+++.--..+..
 
 By comparison, a corresponding article on Haskell (see
 http://en.wikipedia.org/wiki/Haskell_(programming_language)) provided
 the following Haskell alternative::
 
  The following is a Hello world program written in Haskell (note that
  except for the last line all lines can be omitted):
  
  module Main where
  
  main :: IO ()
  main = putStrLn Hello, World!
 
 I became curious about the use of whitespace in the brainfuck example,
 and decided to see if the Haskell code could also be written more
 compactly.  While doing some research on this topic, I discovered a
 Wikibook article (see
 http://en.wikibooks.org/wiki/Haskell/Indentation) that discussed
 indentation in Haskell, and discovered that it was indeed entirely
 possible to write compact code in Haskell, using semicolon[s] to
 separate things and curly braces to group them back.  The following
 four rules were provided to 

[Haskell-cafe] Re: Haskell Forum

2010-07-27 Thread Benjamin L. Russell
Nick Bowler nbow...@elliptictech.com writes:

 On 13:58 Mon 26 Jul , John Meacham wrote:
 There already is an NNTP - mailing list gateway via gmane that gives a
 nice forumy and threaded web interface for those with insufficient email
 readers. Adding a completely different interface seems unnecessary and
 fragmentary.
 
 http://news.gmane.org/gmane.comp.lang.haskell.cafe

 Ah, I didn't realise the gmane web interface supported followups (I knew
 the NNTP interface did, and mentioned this elsewhere in this thread).
 Looks like we've already got a web forum, then, so I guess there's
 nothing to do! :)

Same here.  Why don't we just use this interface, which already exists?

-- Benjamin L. Russell
-- 
Benjamin L. Russell  /   DekuDekuplex at Yahoo dot com
http://dekudekuplex.wordpress.com/
Translator/Interpreter / Mobile:  +011 81 80-3603-6725
Furuike ya, kawazu tobikomu mizu no oto. -- Matsuo Basho^ 

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


Re: [Haskell-cafe] Error Monad and strings

2010-07-27 Thread Antoine Latter
On Tue, Jul 27, 2010 at 6:29 PM, Dietrich Epp d...@zdome.net wrote:
 I'll say yes, a pattern match failure is a bug.  This is one of the great
 debates in the language: whether all pattern matching code should be
 guaranteed complete at compile time or not.  However, any function you call
 which returns a result in your monad could theoretically call fail if it
 was written that way.  Data.Map.lookup used to call fail when it could not
 find a key, but that got changed.

I've always thought that being able to write:

 catMaybes :: [Maybe a] - [a]
 catMaybes xs = [ x | Just x - xs ]

is really cool, which relies on:

 fail _ = []

being in the Monad instance for List.

But I would give that up for getting fail out of Monad. We can alway
re-implement catMaybes.

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


Re: [Haskell-cafe] Chart package segfaults when rendering to window

2010-07-27 Thread briand
On Mon, 26 Jul 2010 21:54:16 -0700
Thomas DuBuisson thomas.dubuis...@gmail.com wrote:

 Can you boil this down to some simple example code?  Are you using a
 recent version of Chart?  And your definition of latest gtk2hs is
 11, right?  How about your gtk+ C library, it what? 2.20?
 

I can run any of the examples from the home page that render to screen.

the AM chart is the one I'm using.

BTW, the AM chart has a bug.  It does not include the proper color
modules and needs a (opaque color) instead of just color.

gtk2hs is 11

gtk+ C library appars to be (debian package) 2.20.1


 
  I was wondering if anybody has been using Chart and may have seen
  the same thing.
 
 Nope, not me.

Yep, figured I'd be suffering alone.

Brian

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


[Haskell-cafe] Need Control.Monad.State

2010-07-27 Thread michael rice
How do I import Control.Monad.State?

I see this note in 
http://en.wikibooks.org/wiki/Haskell/Understanding_monads/State
 
Note: in some package systems used for GHC, the Control.Monad.State module is 
in a separate package, usually indicated by MTL (Monad Transformer Library).

Michael


===rand.hs ==

import Control.Monad.State

type GeneratorState = State StdGen

rollDie :: GeneratorState Int
rollDie = do generator - get
 let( value, newGenerator ) = randomR (1,6) generator
 put newGenerator
 return value

===

[mich...@localhost ~]$ ghci rand
GHCi, version 6.12.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package ffi-1.0 ... linking ... done.

rand.hs:1:7:
    Could not find module `Control.Monad.State':
  Use -v to see a list of the files searched for.
Failed, modules loaded: none.
Prelude




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


Re: [Haskell-cafe] Need Control.Monad.State

2010-07-27 Thread Ivan Miljenovic
On 28 July 2010 12:39, michael rice nowg...@yahoo.com wrote:

 How do I import Control.Monad.State?

Install and use the mtl library (comes with the Haskell platform),
monads-fd (almost identical API to mtl; the point of this is that mtl
uses some extension: the non-extension bits are in the transformers
library and monads-fd extends transformers by using extensions to
implement mtl functionality) or monads-tf (a different approach to
what monads-fd does using different extensions).

To check if you have mtl installed (substitute the other package names
if necessary):

ghc-pkg list mtl

If it isn't installed, you can use cabal-install to install it:

cabal install mtl

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


Re: [Haskell-cafe] Need Control.Monad.State

2010-07-27 Thread michael rice
[mich...@localhost ~]$ ghc-pkg list mtl
/usr/lib/ghc-6.12.1/package.conf.d
[mich...@localhost ~]$ 

Installed?

Michael

--- On Tue, 7/27/10, Ivan Miljenovic ivan.miljeno...@gmail.com wrote:

From: Ivan Miljenovic ivan.miljeno...@gmail.com
Subject: Re: [Haskell-cafe] Need Control.Monad.State
To: michael rice nowg...@yahoo.com
Cc: haskell-cafe@haskell.org
Date: Tuesday, July 27, 2010, 10:51 PM

On 28 July 2010 12:39, michael rice nowg...@yahoo.com wrote:

 How do I import Control.Monad.State?

Install and use the mtl library (comes with the Haskell platform),
monads-fd (almost identical API to mtl; the point of this is that mtl
uses some extension: the non-extension bits are in the transformers
library and monads-fd extends transformers by using extensions to
implement mtl functionality) or monads-tf (a different approach to
what monads-fd does using different extensions).

To check if you have mtl installed (substitute the other package names
if necessary):

ghc-pkg list mtl

If it isn't installed, you can use cabal-install to install it:

cabal install mtl

--
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com



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


Re: [Haskell-cafe] Need Control.Monad.State

2010-07-27 Thread Ivan Miljenovic
On 28 July 2010 13:03, michael rice nowg...@yahoo.com wrote:

 [mich...@localhost ~]$ ghc-pkg list mtl
 /usr/lib/ghc-6.12.1/package.conf.d
 [mich...@localhost ~]$

 Installed?

No; if it was installed it would specify a version.


 Michael

 --- On Tue, 7/27/10, Ivan Miljenovic ivan.miljeno...@gmail.com wrote:

 From: Ivan Miljenovic ivan.miljeno...@gmail.com
 Subject: Re: [Haskell-cafe] Need Control.Monad.State
 To: michael rice nowg...@yahoo.com
 Cc: haskell-cafe@haskell.org
 Date: Tuesday, July 27, 2010, 10:51 PM

 On 28 July 2010 12:39, michael rice nowg...@yahoo.com wrote:
 
  How do I import Control.Monad.State?

 Install and use the mtl library (comes with the Haskell platform),
 monads-fd (almost identical API to mtl; the point of this is that mtl
 uses some extension: the non-extension bits are in the transformers
 library and monads-fd extends transformers by using extensions to
 implement mtl functionality) or monads-tf (a different approach to
 what monads-fd does using different extensions).

 To check if you have mtl installed (substitute the other package names
 if necessary):

 ghc-pkg list mtl

 If it isn't installed, you can use cabal-install to install it:

 cabal install mtl

 --
 Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com
 IvanMiljenovic.wordpress.com




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


Re: [Haskell-cafe] Need Control.Monad.State

2010-07-27 Thread Felipe Lessa
On Wed, Jul 28, 2010 at 12:04 AM, Ivan Miljenovic
ivan.miljeno...@gmail.com wrote:
 On 28 July 2010 13:03, michael rice nowg...@yahoo.com wrote:

 [mich...@localhost ~]$ ghc-pkg list mtl
 /usr/lib/ghc-6.12.1/package.conf.d
 [mich...@localhost ~]$

 Installed?

 No; if it was installed it would specify a version.

For example:

$ ghc-pkg list mtl
/usr/lib64/ghc-6.12.3/package.conf.d
   mtl-1.1.0.2

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


Re: [Haskell-cafe] Need Control.Monad.State

2010-07-27 Thread michael rice
See below. Lot's of warnings. Is the install OK? If so, can I use the same 
*import*?

Michael

--- On Tue, 7/27/10, Ivan Miljenovic ivan.miljeno...@gmail.com wrote:


 If it isn't installed, you can use cabal-install to install it:

 cabal install mtl

 --
 Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com
 IvanMiljenovic.wordpress.com



[mich...@localhost ~]$ cabal install mtl
Resolving dependencies...
Downloading mtl-1.1.0.2...
Configuring mtl-1.1.0.2...
Preprocessing library mtl-1.1.0.2...
Building mtl-1.1.0.2...
[ 1 of 21] Compiling Control.Monad.Identity ( Control/Monad/Identity.hs, 
dist/build/Control/Monad/Identity.o )

Control/Monad/Cont.hs:1:11:
    Warning: -fallow-undecidable-instances is deprecated: use 
-XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

Control/Monad/Cont/Class.hs:1:11:
    Warning: -fallow-undecidable-instances is deprecated: use 
-XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

Control/Monad/Error.hs:1:11:
    Warning: -fallow-undecidable-instances is deprecated: use 
-XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

Control/Monad/Error/Class.hs:1:11:
    Warning: -fallow-undecidable-instances is deprecated: use 
-XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

Control/Monad/Identity.hs:1:0:
    Warning: Module `Prelude' is deprecated:
   You are using the old package `base' version 3.x.
   Future GHC versions will not support base version 3.x. You
   should update your code to use the new base version 4.x.

Control/Monad/List.hs:1:11:
    Warning: -fallow-undecidable-instances is deprecated: use 
-XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

Control/Monad/RWS/Lazy.hs:1:11:
    Warning: -fallow-undecidable-instances is deprecated: use 
-XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

Control/Monad/RWS/Strict.hs:1:11:
    Warning: -fallow-undecidable-instances is deprecated: use 
-XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

Control/Monad/Reader.hs:2:11:
    Warning: -fallow-undecidable-instances is deprecated: use 
-XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

Control/Monad/Reader/Class.hs:1:11:
    Warning: -fallow-undecidable-instances is deprecated: use 
-XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

Control/Monad/State/Lazy.hs:1:11:
    Warning: -fallow-undecidable-instances is deprecated: use 
-XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

Control/Monad/State/Strict.hs:1:11:
    Warning: -fallow-undecidable-instances is deprecated: use 
-XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

Control/Monad/Writer.hs:1:11:
    Warning: -fallow-undecidable-instances is deprecated: use 
-XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

Control/Monad/Writer/Class.hs:1:11:
    Warning: -fallow-undecidable-instances is deprecated: use 
-XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

Control/Monad/Writer/Lazy.hs:1:11:
    Warning: -fallow-undecidable-instances is deprecated: use 
-XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

Control/Monad/Writer/Strict.hs:1:11:
    Warning: -fallow-undecidable-instances is deprecated: use 
-XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead
[ 2 of 21] Compiling Control.Monad.Writer.Class ( 
Control/Monad/Writer/Class.hs, dist/build/Control/Monad/Writer/Class.o )

Control/Monad/Writer/Class.hs:1:0:
    Warning: Module `Prelude' is deprecated:
   You are using the old package `base' version 3.x.
   Future GHC versions will not support base version 3.x. You
   should update your code to use the new base version 4.x.
[ 3 of 21] Compiling Control.Monad.Error.Class ( Control/Monad/Error/Class.hs, 
dist/build/Control/Monad/Error/Class.o )

Control/Monad/Error/Class.hs:1:0:
    Warning: Module `Prelude' is deprecated:
   You are using the old package `base' version 3.x.
   Future GHC versions will not support base version 3.x. You
   should update your code to use the new base version 4.x.
[ 4 of 21] Compiling Control.Monad.State.Class ( Control/Monad/State/Class.hs, 
dist/build/Control/Monad/State/Class.o )

Control/Monad/State/Class.hs:1:0:
    Warning: Module `Prelude' is deprecated:
   You are using the old package `base' version 3.x.
   Future GHC versions will not support base version 3.x. You
   should update your code to use the new base version 4.x.
[ 5 of 21] Compiling Control.Monad.Reader.Class ( 
Control/Monad/Reader/Class.hs, dist/build/Control/Monad/Reader/Class.o )

Control/Monad/Reader/Class.hs:1:0:
    Warning: Module `Prelude' is 

Re: [Haskell-cafe] Need Control.Monad.State

2010-07-27 Thread Ivan Miljenovic
On 28 July 2010 13:17, michael rice nowg...@yahoo.com wrote:

 See below. Lot's of warnings. Is the install OK? If so, can I use the same 
 *import*?

Yeah, the install is OK.  The meaning of the warnings are:

* Warning: -fallow-undecidable-instances is deprecated: this GHC
option has changed name, but the mtl package still uses the old name.

* Warning: Module `Prelude' is deprecated: mtl doesn't specify any
bounds on the version of the base library to be used (mainly because
of historic reasons when it wasn't changing much and the Haskell
community wasn't stressing versioning as much; note that the last
version of mtl was released almost 2 years ago).  Because a lot of
packages broke when GHC-6.10.4 started shipping with base-4 (along
with base-3 for compatability purposes) due to the differences in how
exceptions were handled, if there is no upper bound on the version of
base to be used then cabal-install plays it safe and uses base-3.
However, the next version of GHC (6.14, which should be coming out
later this year) will not ship with base-3, so GHC-6.12 included that
warning message for people that kept trying to use base-3 that their
code won't work with 6.14.

So yes, now you can use import Control.Monad.State.


 Michael

 --- On Tue, 7/27/10, Ivan Miljenovic ivan.miljeno...@gmail.com wrote:

 
  If it isn't installed, you can use cabal-install to install it:
 
  cabal install mtl
 
  --
  Ivan Lazar Miljenovic
  ivan.miljeno...@gmail.com
  IvanMiljenovic.wordpress.com
 


 [mich...@localhost ~]$ cabal install mtl
 Resolving dependencies...
 Downloading mtl-1.1.0.2...
 Configuring mtl-1.1.0.2...
 Preprocessing library mtl-1.1.0.2...
 Building mtl-1.1.0.2...
 [ 1 of 21] Compiling Control.Monad.Identity ( Control/Monad/Identity.hs, 
 dist/build/Control/Monad/Identity.o )

 Control/Monad/Cont.hs:1:11:
     Warning: -fallow-undecidable-instances is deprecated: use 
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

 Control/Monad/Cont/Class.hs:1:11:
     Warning: -fallow-undecidable-instances is deprecated: use 
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

 Control/Monad/Error.hs:1:11:
     Warning: -fallow-undecidable-instances is deprecated: use 
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

 Control/Monad/Error/Class.hs:1:11:
     Warning: -fallow-undecidable-instances is deprecated: use 
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

 Control/Monad/Identity.hs:1:0:
     Warning: Module `Prelude' is deprecated:
    You are using the old package `base' version 3.x.
    Future GHC versions will not support base version 3.x. You
    should update your code to use the new base version 4.x.

 Control/Monad/List.hs:1:11:
     Warning: -fallow-undecidable-instances is deprecated: use 
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

 Control/Monad/RWS/Lazy.hs:1:11:
     Warning: -fallow-undecidable-instances is deprecated: use 
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

 Control/Monad/RWS/Strict.hs:1:11:
     Warning: -fallow-undecidable-instances is deprecated: use 
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

 Control/Monad/Reader.hs:2:11:
     Warning: -fallow-undecidable-instances is deprecated: use 
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

 Control/Monad/Reader/Class.hs:1:11:
     Warning: -fallow-undecidable-instances is deprecated: use 
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

 Control/Monad/State/Lazy.hs:1:11:
     Warning: -fallow-undecidable-instances is deprecated: use 
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

 Control/Monad/State/Strict.hs:1:11:
     Warning: -fallow-undecidable-instances is deprecated: use 
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

 Control/Monad/Writer.hs:1:11:
     Warning: -fallow-undecidable-instances is deprecated: use 
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

 Control/Monad/Writer/Class.hs:1:11:
     Warning: -fallow-undecidable-instances is deprecated: use 
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

 Control/Monad/Writer/Lazy.hs:1:11:
     Warning: -fallow-undecidable-instances is deprecated: use 
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead

 Control/Monad/Writer/Strict.hs:1:11:
     Warning: -fallow-undecidable-instances is deprecated: use 
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-} instead
 [ 2 of 21] Compiling Control.Monad.Writer.Class ( 
 Control/Monad/Writer/Class.hs, dist/build/Control/Monad/Writer/Class.o )

 Control/Monad/Writer/Class.hs:1:0:
     Warning: Module `Prelude' is deprecated:
   

Re: [Haskell-cafe] Need Control.Monad.State

2010-07-27 Thread aditya siram
I didn't realize the State monad wasn't part of the base install. Any
particular reason for this?
-deech

On Tue, Jul 27, 2010 at 10:24 PM, Ivan Miljenovic ivan.miljeno...@gmail.com
 wrote:

 On 28 July 2010 13:17, michael rice nowg...@yahoo.com wrote:
 
  See below. Lot's of warnings. Is the install OK? If so, can I use the
 same *import*?

 Yeah, the install is OK.  The meaning of the warnings are:

 * Warning: -fallow-undecidable-instances is deprecated: this GHC
 option has changed name, but the mtl package still uses the old name.

 * Warning: Module `Prelude' is deprecated: mtl doesn't specify any
 bounds on the version of the base library to be used (mainly because
 of historic reasons when it wasn't changing much and the Haskell
 community wasn't stressing versioning as much; note that the last
 version of mtl was released almost 2 years ago).  Because a lot of
 packages broke when GHC-6.10.4 started shipping with base-4 (along
 with base-3 for compatability purposes) due to the differences in how
 exceptions were handled, if there is no upper bound on the version of
 base to be used then cabal-install plays it safe and uses base-3.
 However, the next version of GHC (6.14, which should be coming out
 later this year) will not ship with base-3, so GHC-6.12 included that
 warning message for people that kept trying to use base-3 that their
 code won't work with 6.14.

 So yes, now you can use import Control.Monad.State.

 
  Michael
 
  --- On Tue, 7/27/10, Ivan Miljenovic ivan.miljeno...@gmail.com wrote:
 
  
   If it isn't installed, you can use cabal-install to install it:
  
   cabal install mtl
  
   --
   Ivan Lazar Miljenovic
   ivan.miljeno...@gmail.com
   IvanMiljenovic.wordpress.com
  
 
 
  [mich...@localhost ~]$ cabal install mtl
  Resolving dependencies...
  Downloading mtl-1.1.0.2...
  Configuring mtl-1.1.0.2...
  Preprocessing library mtl-1.1.0.2...
  Building mtl-1.1.0.2...
  [ 1 of 21] Compiling Control.Monad.Identity ( Control/Monad/Identity.hs,
 dist/build/Control/Monad/Identity.o )
 
  Control/Monad/Cont.hs:1:11:
  Warning: -fallow-undecidable-instances is deprecated: use
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-}
 instead
 
  Control/Monad/Cont/Class.hs:1:11:
  Warning: -fallow-undecidable-instances is deprecated: use
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-}
 instead
 
  Control/Monad/Error.hs:1:11:
  Warning: -fallow-undecidable-instances is deprecated: use
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-}
 instead
 
  Control/Monad/Error/Class.hs:1:11:
  Warning: -fallow-undecidable-instances is deprecated: use
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-}
 instead
 
  Control/Monad/Identity.hs:1:0:
  Warning: Module `Prelude' is deprecated:
 You are using the old package `base' version 3.x.
 Future GHC versions will not support base version 3.x. You
 should update your code to use the new base version 4.x.
 
  Control/Monad/List.hs:1:11:
  Warning: -fallow-undecidable-instances is deprecated: use
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-}
 instead
 
  Control/Monad/RWS/Lazy.hs:1:11:
  Warning: -fallow-undecidable-instances is deprecated: use
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-}
 instead
 
  Control/Monad/RWS/Strict.hs:1:11:
  Warning: -fallow-undecidable-instances is deprecated: use
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-}
 instead
 
  Control/Monad/Reader.hs:2:11:
  Warning: -fallow-undecidable-instances is deprecated: use
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-}
 instead
 
  Control/Monad/Reader/Class.hs:1:11:
  Warning: -fallow-undecidable-instances is deprecated: use
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-}
 instead
 
  Control/Monad/State/Lazy.hs:1:11:
  Warning: -fallow-undecidable-instances is deprecated: use
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-}
 instead
 
  Control/Monad/State/Strict.hs:1:11:
  Warning: -fallow-undecidable-instances is deprecated: use
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-}
 instead
 
  Control/Monad/Writer.hs:1:11:
  Warning: -fallow-undecidable-instances is deprecated: use
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-}
 instead
 
  Control/Monad/Writer/Class.hs:1:11:
  Warning: -fallow-undecidable-instances is deprecated: use
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-}
 instead
 
  Control/Monad/Writer/Lazy.hs:1:11:
  Warning: -fallow-undecidable-instances is deprecated: use
 -XUndecidableInstances or pragma {-# LANGUAGE UndecidableInstances #-}
 instead
 
  Control/Monad/Writer/Strict.hs:1:11:
  Warning: -fallow-undecidable-instances is deprecated: use
 

Re: [Haskell-cafe] new Cabal user question -- installing to Haskell Platform on Windows network drive?

2010-07-27 Thread Rogan Creswick
On Tue, Jul 27, 2010 at 2:43 PM, Peter Schmitz ps.hask...@gmail.com wrote:
 So, by default, cabal wants to put its config and updates on C:.

 I looked at C:\Documents and Settings\pschmitz\Application Data\cabal\config

 It has various references to C:, some commented out. E.g.:

 remote-repo-cache: C:\Documents and Settings\pschmitz\Application
 Data\cabal\packages

 build-summary: C:\Documents and Settings\pschmitz\Application
 Data\cabal\logs\build.log

 install-dirs user
 -- prefix: C:\\Documents and Settings\\pschmitz\\Application Data\\cabal

You can change these to whatever you want, and cabal should just start
using those locations, if that helps.

 Given that I want to keep everything on H:,
 and assuming that I don't want to place the Cabal configs and updates in the
 Platform tree (H:\proc\tools\Haskell Platform),
 I would _like_ to create a dir such as
 H:\proc\tools\cabal
 to hold everything that Cabal would normally put on C:.

 *** I'm afraid I'm having trouble figuring out how to accomplish this.

 Is there (hopefully) a combination of cabal command line switches that will
 create a new config file over on H: for me,
 or must I edit the config file directly and move it to H:?

There are others on this list that know cabal much better than I, but
I have been working with it a bit recently, so I'll take a stab..

I don't believe you can configure *cabal* to look on H: for the cabal
config, without specifying .  I believe it uses the windows
Application Data directory for your current user to locate the cabal
config (there is a windows system (?) call that returns something akin
to c:\Documents and Settings\username\Application Data\ ).  You *can*
change the location of your Application Data directory by hacking the
windows registry, but that is likely to cause more pain than it is
worth.

I think you will be best served by just editing the entries in your
cabal config (if that, even) unless you have a very good reason to
relocate the cabal config itself.

(Ok, so I think I lied a little -- iirc, there is an undocumented
cabal flag that will let you specify the path to the cabal config file
to use.  I think it has to be the first parameter to cabal, and I
think it's --cabal-config=file, but I've only used it once and I
don't think it's really worth the trouble in your case. Application
Data is a pretty standard place for things like this.)

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


Re: [Haskell-cafe] Need Control.Monad.State

2010-07-27 Thread Ivan Miljenovic
On 28 July 2010 14:07, aditya siram aditya.si...@gmail.com wrote:
 I didn't realize the State monad wasn't part of the base install. Any
 particular reason for this?

Because there's no reason for it to be?  GHC is bundled with enough
libraries as it is (and with the exception of Cabal, it's not safe to
upgrade any of them).

However, mtl _is_ part of the Haskell Platform, so in that sense it's
part of the _recommended_ base install...

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


Re: [Haskell-cafe] Int and ByteStrings

2010-07-27 Thread wren ng thornton

Don Stewart wrote:

wren:

Hey all,

Is there a library function (f :: [Int] - ByteString) such that it's  
prefix-preserving, and platform independent? GHC-only is fine for now.  
There are a bunch of functions of that type, but I need those guarantees  
and I'm hoping someone else has already done it.


should be possible to write using Data.Binary.


Definitely possible, I was just hoping it's already been done :)

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