Re: [Haskell-cafe] Stacking data types

2011-04-11 Thread Job Vranish
Yep you probably don't need the fundep, you just might need to provide more
signatures. It does imply one 'b' for an 'a' which probably isn't what you
want.

On Wed, Apr 6, 2011 at 6:13 PM, Yves Parès limestr...@gmail.com wrote:

 Thank you all,

 In fact, Brandon, I knew about Datatypes a la carte, I just found it overly
 complicated.

 Thanks for you solution, Job. However (and even if it doesn't work without
 it) I fail to see why you need the functional dependency on Has...
 Doesn't it implies here that for one 'a' there can only be one 'b' such as
 'Has b a'?



 2011/4/6 Job Vranish job.vran...@gmail.com

 I think you want something like this:

 {-# Language MultiParamTypeClasses
, FlexibleInstances
, FunctionalDependencies
, UndecidableInstances
, FlexibleContexts
, OverlappingInstances

#-}
 data Character a = Character { life :: Int,
charaInner :: a }
   deriving (Show)

 data Gun a = Gun { firepower :: Int,
gunInner :: a }
  deriving (Show)

 data Armor a = Armor { resistance :: Int,
armorInner :: a }
deriving (Show)


 class HasInner f where
   getInner :: f a - a

 instance HasInner Character where
   getInner = charaInner

 instance HasInner Gun where
   getInner = gunInner

 instance HasInner Armor where
   getInner = armorInner


 class Has b a | a - b where
 content :: a - b

 instance (Has b a, HasInner f) = Has b (f a) where
 content a = content $ getInner a

 instance (HasInner f) = Has a (f a) where
 content a = getInner a

 chara = Character 100 $ Armor 40 $ Gun 12 ()

 itsGun :: (Has (Gun b) a) = a - Gun b
 itsGun = content

 You were missing a mechanism to extract the inner value from your
 datatypes.

 - Job


 On Wed, Apr 6, 2011 at 2:57 PM, Yves Parès limestr...@gmail.com wrote:

 Hello Café,

 I'm trying to get some modular data types.
 The idea that came to me is that I could stack them, for instance :

 data Character a = Character { life :: Int,
charaInner :: a }

 data Gun a = Gun { firepower :: Int,
gunInner :: a }

 data Armor a = Armor { resistance :: Int,
armorInner :: a }

 Then a character with a gun and an armor can be build this way:

 chara = Character 100 $ Armor 40 $ Gun 12

 The idea now is to be able to get some part of the character:

 itsGun :: Character ?? - Gun ??
 itsGun = content

 Then content would be a class method:

 class Has b a where
 content :: a - b

 And it would be recursively defined so that:

 instance (Has c b, Has b a) = Has c a where
 content = (content :: b - c) . (content :: a - b)

 Then itsGun would be more like:

 itsGun :: (Has Gun a) = a - Gun ??
 itsGun = content

 But after some juggling with extensions (ScopedTypeVariables,
 UndecidableInstances, IncoherentInstances...) I can't get it working.

 Has someone a simpler way to achieve modular types?

 ___
 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] Stacking data types

2011-04-06 Thread Job Vranish
I think you want something like this:

{-# Language MultiParamTypeClasses
   , FlexibleInstances
   , FunctionalDependencies
   , UndecidableInstances
   , FlexibleContexts
   , OverlappingInstances

   #-}
data Character a = Character { life :: Int,
   charaInner :: a }
  deriving (Show)

data Gun a = Gun { firepower :: Int,
   gunInner :: a }
 deriving (Show)

data Armor a = Armor { resistance :: Int,
   armorInner :: a }
   deriving (Show)


class HasInner f where
  getInner :: f a - a

instance HasInner Character where
  getInner = charaInner

instance HasInner Gun where
  getInner = gunInner

instance HasInner Armor where
  getInner = armorInner


class Has b a | a - b where
content :: a - b

instance (Has b a, HasInner f) = Has b (f a) where
content a = content $ getInner a

instance (HasInner f) = Has a (f a) where
content a = getInner a

chara = Character 100 $ Armor 40 $ Gun 12 ()

itsGun :: (Has (Gun b) a) = a - Gun b
itsGun = content

You were missing a mechanism to extract the inner value from your datatypes.

- Job


On Wed, Apr 6, 2011 at 2:57 PM, Yves Parès limestr...@gmail.com wrote:

 Hello Café,

 I'm trying to get some modular data types.
 The idea that came to me is that I could stack them, for instance :

 data Character a = Character { life :: Int,
charaInner :: a }

 data Gun a = Gun { firepower :: Int,
gunInner :: a }

 data Armor a = Armor { resistance :: Int,
armorInner :: a }

 Then a character with a gun and an armor can be build this way:

 chara = Character 100 $ Armor 40 $ Gun 12

 The idea now is to be able to get some part of the character:

 itsGun :: Character ?? - Gun ??
 itsGun = content

 Then content would be a class method:

 class Has b a where
 content :: a - b

 And it would be recursively defined so that:

 instance (Has c b, Has b a) = Has c a where
 content = (content :: b - c) . (content :: a - b)

 Then itsGun would be more like:

 itsGun :: (Has Gun a) = a - Gun ??
 itsGun = content

 But after some juggling with extensions (ScopedTypeVariables,
 UndecidableInstances, IncoherentInstances...) I can't get it working.

 Has someone a simpler way to achieve modular types?

 ___
 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] Missing MaybeT MonadFix instance

2011-04-01 Thread Job Vranish
Is there a particular reason that the
transformershttp://hackage.haskell.org/packages/archive/transformers/latest/doc/html/Control-Monad-Trans-Maybe.html#v:MaybeTversion
of the MaybeT monad does not have a MonadFix instance?

It seems like the following instance would be suitable:

instance (MonadFix m) = MonadFix (MaybeT m) where
  mfix f = MaybeT $ mfix $ \a - runMaybeT $ f $ case a of
 Just a - a
 Nothing - error mfix MaybeT: Nothing

I don't think it's possible to hit the error case:
In order to terminate f cannot be strict so it must return a value without
evaluating its input. If f returns a Nothing, then you have your return
value and you're done. If f returns a Just, then we don't hit the error
case.

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


Re: [Haskell-cafe] makeTokenParser + LanguageDef

2011-03-08 Thread Job Vranish
The tutorial here:
http://legacy.cs.uu.nl/daan/download/parsec/parsec.html#Lexical analysis
http://legacy.cs.uu.nl/daan/download/parsec/parsec.html#Lexical analysisis
for parsec 2, but it's still quite relevant.

- Job

On Tue, Mar 8, 2011 at 6:22 AM, Hauschild, Klaus (EXT) 
klaus.hauschild@siemens.com wrote:

  Hi Haskellers,

 is there a fine tutorial for building a parser with parsecs (3.*)
 makeTokenParser and LanguageDef stuff?

 Klaus


 ___
 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] Convert a function to a string of operators?

2011-03-04 Thread Job Vranish
Make your own expression type and make it an instance of the Num typeclass.
Then you can build your expression using the usual operators and then use
show to convert to a string.

For example:
https://github.com/jvranish/grhug/blob/master/SymbolicDifferentiation/SymbolicDifferentiation.hs

It probably does more than you want, but you should be able to get the basic
idea.

The really slick thing about it is that you can use expression type on any
function that takes a Num and you'll get a representation of the computation
that took place to get the result.

For example:
  show (baw a b c :: Int)  -- will show you an int
and
  show (baw a b c :: Expr)  -- will give you (a + b) * c  (well... a, b, c
will be replace by whatever you passed in, but you can make them variable
names just the same)

- Job


On Fri, Mar 4, 2011 at 3:32 PM, Evgeny Grablyk evgeny.grab...@gmail.comwrote:

 Hello!

 I was wondering if it was possible to convert a function (which may
 also call functions) to a plain list of operators on parameters.
 Example:

 foo a b = a + b
 bar a b = a * b

 baw a b c = bar (foo a b) c
 baw' a b c = (a + b) * c

 Any way to get `baw'' from `baw'?  Preferrably as a String.

 --
 Evgeny

 ___
 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] Infinite types should be optionally allowed

2011-02-22 Thread Job Vranish
Thanks,
Perhaps my algorithm works then. I shall have to read up more on these
things :)

- Job

On Mon, Feb 21, 2011 at 4:54 PM, Luke Palmer lrpal...@gmail.com wrote:

 On Sun, Feb 20, 2011 at 6:01 PM, Job Vranish jvran...@gmail.com wrote:
  My current algorithm says that neither of the types you gave is strictly
  more general than the other, which I'm guessing is probably not true. I'm
  curious what the correct answer is and would appreciate someone pointing
 out
  the flaw in my reasoning/code :)

 I don't remember how I constructed those terms, and I admit that I was
 arguing out of my depth.  I really should have exposed my construction
 -- we're all good engineers here, we know the difference between an
 algorithm and intuition.

 Things I have read since have suggested that I was wrong.  Pierce's
 Types and Programming Languages has a chapter on equi-recursive types
 which, if it does not provide insight itself, I'm sure has references
 to papers that go into all the detail needed to answer this technical
 question.

 Luke

  My test code is on github here:
 https://github.com/jvranish/InfiniteTypes
  Also, is there a book you'd recommend that would explain this in further
  detail?
  Thanks,
  - Job
 
  On Mon, Feb 16, 2009 at 5:16 PM, Luke Palmer lrpal...@gmail.com wrote:
 
  On Sat, Feb 14, 2009 at 2:06 PM, Job Vranish jvran...@gmail.com
 wrote:
 
  I'm pretty sure that the problem is decidable, at least with haskell
  98 types (other type extensions may complicate things a bit). It ends
  up being a graph unification algorithm. I've tried some simple
  algorithms and they seem to work.
 
  What do you mean by the inference engine is only half of the story?
  From what I understand, the inference engine infers types via
  unification, if the types unify, then the unified types are the
  inferred types, if the types don't unify, then type check fails. Am I
  missing/misunderstanding  something?
 
  Sorry it took me so long to respond.  It took a while to formulate this
  example.
 
  Here are two (convoluted) functions, passed to the fixtypes inference
  engine:
 
  Expr y (b (c i) (c (b b (b c (c i)
  (fix b . (a - b - (a - c - d) - d) - c) - c
  Expr y (b (c i) (b (c (b b (b c (c i (b (c i) k)))
  (fix c . ((a - ((b - c) - d) - (a - d - e) - e) - f) - f)
 
  These are somewhat complex types; sorry about that.  But here's a
  challenge:  is one of these types more general than the other?  For
 example,
  if you wrote the first term and gave the second signature, should it
  typecheck?  If you figure it out, can you give an algorithm for doing
 so?
 
  I'm not going to say how I came up with these functions, because that
  would give away the answer :-)
 
  Luke
 
 
 
  I almost think that the problem might be solvable by just generating
  the appropriate newtype whenever an infinite type shows up, and doing
  the wrapping/unwrapping behind the scenes. This would be a hacked up
  way to do it, but I think it would work.
 
 
  On Fri, Feb 13, 2009 at 6:09 PM, Luke Palmer lrpal...@gmail.com
 wrote:
   On Fri, Feb 13, 2009 at 4:04 PM, Luke Palmer lrpal...@gmail.com
   wrote:
  
   On Fri, Feb 13, 2009 at 3:13 PM, Job Vranish jvran...@gmail.com
   wrote:
  
   There are good reasons against allowing infinite types by default
   (mostly, that a lot of things type check that are normally not what
   we
   want). An old haskell cafe conversation on the topic is here:
  
  
  
 http://www.nabble.com/There%27s-nothing-wrong-with-infinite-types!-td7713737.html
  
   However, I think infinite types should be allowed, but only with an
   explicit type signature. In other words, don't allow infinite types
   to
   be inferred, but if they are specified, let them pass. I think it
   would be very hard to shoot yourself in the foot this way.
  
   Oops!  I'm sorry, I completely misread the proposal.  Or read it
   correctly,
   saw an undecidability hiding in there, and got carried away.
  
   What you are proposing is called equi-recursive types, in contrast to
   the
   more popular iso-recursive types (which Haskell uses).  There are
   plentiful
   undecidable problems with equi-recursive types, but there are ways to
   pull
   it off.  The question is whether these ways play nicely with
 Haskell's
   type
   system.
  
   But because of the fundamental computational problems associated,
 there
   needs to be a great deal of certainty that this is even possible
 before
   considering its language design implications.
  
  
   That inference engine seems to be a pretty little proof-of-concept,
   doesn't it?  But it is sweeping some very important stuff under the
   carpet.
  
   The proposal is to infer the type of a term,  then check it against
 an
   annotation.  Thus every program is well-typed, but it's the
 compiler's
   job
   to check that it has the type the user intended.  I like the idea.
  
   But the inference engine is only half of the story.  It does no type
   checking.  Although

Re: [Haskell-cafe] monadic plumbing

2011-02-22 Thread Job Vranish
You need the MaybeT and EitherT monad transformers:
http://hackage.haskell.org/packages/archive/MaybeT/0.1.2/doc/html/Control-Monad-Maybe.html
http://hackage.haskell.org/packages/archive/MaybeT/0.1.2/doc/html/Control-Monad-Maybe.html
http://hackage.haskell.org/packages/archive/EitherT/0.0.1/doc/html/Control-Monad-Either.html

http://hackage.haskell.org/packages/archive/EitherT/0.0.1/doc/html/Control-Monad-Either.htmlWith
MaybeT, you can wrap foo, bar, and baz with a MaybeT constructor, which
gives you a new monad that you can compose the usual way.

For example:

result - runMaybeT (MaybeT foo = MaybeT bar = MaybeT baz)
case result of
  Just x - ...
  Nothing - ...

- Job

On Tue, Feb 22, 2011 at 4:03 PM, Alberto G. Corona agocor...@gmail.comwrote:

 Recently I had to navigatate trough data structures chained with mutable
 referenes in th STM monad. The problem is that their values are enveloped in
  Either or Maybe results.

 functional compositions in the Either of Maybe , or list  monads are not
 possible when the values are  embedded inside effect monads (i.e. STM or IO)
 . I tried  to find some trick to handle it.

 to summarize, given:

  foo, :  a - m (Maybe b)
  bar :   b - m (Maybe c)
  baz :  c - m (Maybe d)

 how to compose foo bar and baz? Or, at least,  Are something out there to
 handle it in the less painful way?.


 I solved the generalized problem  (chaining  any double monadic
 combination) with a sort of monadic connector that acts as a  double
 monadic operator   ==  so that

 return. return (x :: a) == foo == bar == baz

 can be possible. Although I don't know if  it is the best solution. I
 wonder why nobody has written about it before:

 class (Monad m, Monad n) = Bimonad m n where
  (=)   ::  n a - (a - m(n b)) - m(n b)

 (==) :: (Bimonad m n) = m (n a) - (a - m(n b)) - m (n b)
 (==) x  f =  x = \y - y =  f

 x  f = x == \ _- f

 infixl 1 ==, 

 The instance for handling the Maybe monad under any other monad is very
 similar to the definition of the normal monad:

 instance (Monad m) = Bimonad m Maybe where
Just x  = f = f x
Nothing = _ = return $ Nothing





 ___
 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] Infinite types should be optionally allowed

2011-02-21 Thread Job Vranish
On Sun, Feb 20, 2011 at 8:56 PM, Brandon Moore brandon_m_mo...@yahoo.comwrote:


 Typechecking with regular types isn't hard.


So do I have the right idea then? To check against a signature, I can just
unify the two types and then check if the unified type is 'equivalent' (is
there a special word for this kind of equivalence?) to the original
signature?
I've gotten the impression from multiple people that type checking with
infinite types is hard. Maybe this isn't so?


 The problem is, the type system
 is almost useless for catching bad programs. Every closed lambda expression
 is typeable if infinite types are allowed.


Yes, this part I understand quite well :)

Usually systems add some sort of

ad-hoc restriction on regular types, like requiring that all all cycles
 pas through

a record type.


Yeah, what I really want is just a better ad-hoc restriction or annotation.
I quite routinely work with code that would be much more simple and elegant
with infinite types.

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


Re: [Haskell-cafe] Faster timeout but is it correct?

2011-02-21 Thread Job Vranish
I'm curious, is it possible that your new timeout implementation would fix
this problem?:

doesntWork :: Int - Int
doesntWork x = last $ cycle [x]

test :: IO (Maybe Bool)
test = timeout 1 $ evaluate $ doesntWork 5 == 5 -- never terminates, even
with the timeout

From what I can gather, this problem is caused by a lack of context switches
in the code for 'doesntWork' so I doubt that a new implementation of timeout
would fix it, but I thought I'd ask :)

It's super annoying, especially when it happens when you're not expecting
it.

(btw, I've only tested the above code in ghc 6.x, so I have no idea if the
behavior is the same in 7)

- Job

On Mon, Feb 21, 2011 at 3:39 PM, Bas van Dijk v.dijk@gmail.com wrote:

 On 19 February 2011 00:04, Bas van Dijk v.dijk@gmail.com wrote:
  So, since the new implementation is not really faster in a
  representative benchmark and above all is buggy, I'm planning to ditch
  it in favour of the event-manager based timeout.

 The patch is ready for review:


 http://hackage.haskell.org/trac/ghc/attachment/ticket/4963/faster_timeout.dpatch

 Bas

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

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


Re: [Haskell-cafe] Infinite types should be optionally allowed

2011-02-20 Thread Job Vranish
Sorry for bringing back an ancient thread but I'd still like to understand
this better.

It is still not obvious to me why typechecking infinite types is so hard. Is
determining type 'equivalence' the hard part? or is that a separate issue?


I wrote a simple infinite type inferer and made an attempt at an algorithm
that can answer your question.

The algorithm works like this: Given two types *a* and *b*: unify *a* with *
b*, if the resulting type is 'equivalent' to the original *a,* then *b* must
be (I think) at least as general as *a*.

To determine equivalence, I start with the head of both types (which are
represented as graphs) and check to see if the constructors are the same. If
they are then I set those two nodes 'equal' and recurse with the children.
It's a 'destructive' algorithm that effectively 'zips' the two graphs
together. It returns false if it encounters two constructors that are
different.


My current algorithm says that neither of the types you gave is strictly
more general than the other, which I'm guessing is probably not true. I'm
curious what the correct answer is and would appreciate someone pointing out
the flaw in my reasoning/code :)

My test code is on github here: https://github.com/jvranish/InfiniteTypes

Also, is there a book you'd recommend that would explain this in further
detail?

Thanks,

- Job


On Mon, Feb 16, 2009 at 5:16 PM, Luke Palmer lrpal...@gmail.com wrote:

 On Sat, Feb 14, 2009 at 2:06 PM, Job Vranish jvran...@gmail.com wrote:

 I'm pretty sure that the problem is decidable, at least with haskell
 98 types (other type extensions may complicate things a bit). It ends
 up being a graph unification algorithm. I've tried some simple
 algorithms and they seem to work.

 What do you mean by the inference engine is only half of the story?
 From what I understand, the inference engine infers types via
 unification, if the types unify, then the unified types are the
 inferred types, if the types don't unify, then type check fails. Am I
 missing/misunderstanding  something?


 Sorry it took me so long to respond.  It took a while to formulate this
 example.

 Here are two (convoluted) functions, passed to the fixtypes inference
 engine:

 Expr y (b (c i) (c (b b (b c (c i)
 (fix b . (a - b - (a - c - d) - d) - c) - c
 Expr y (b (c i) (b (c (b b (b c (c i (b (c i) k)))
 (fix c . ((a - ((b - c) - d) - (a - d - e) - e) - f) - f)

 These are somewhat complex types; sorry about that.  But here's a
 challenge:  is one of these types more general than the other?  For example,
 if you wrote the first term and gave the second signature, should it
 typecheck?  If you figure it out, can you give an algorithm for doing so?

 I'm not going to say how I came up with these functions, because that would
 give away the answer :-)

 Luke



 I almost think that the problem might be solvable by just generating
 the appropriate newtype whenever an infinite type shows up, and doing
 the wrapping/unwrapping behind the scenes. This would be a hacked up
 way to do it, but I think it would work.


 On Fri, Feb 13, 2009 at 6:09 PM, Luke Palmer lrpal...@gmail.com wrote:
  On Fri, Feb 13, 2009 at 4:04 PM, Luke Palmer lrpal...@gmail.com
 wrote:
 
  On Fri, Feb 13, 2009 at 3:13 PM, Job Vranish jvran...@gmail.com
 wrote:
 
  There are good reasons against allowing infinite types by default
  (mostly, that a lot of things type check that are normally not what we
  want). An old haskell cafe conversation on the topic is here:
 
 
 http://www.nabble.com/There%27s-nothing-wrong-with-infinite-types!-td7713737.htmlhttp://www.nabble.com/There%27s-nothing-wrong-with-infinite-types%21-td7713737.html
 
  However, I think infinite types should be allowed, but only with an
  explicit type signature. In other words, don't allow infinite types to
  be inferred, but if they are specified, let them pass. I think it
  would be very hard to shoot yourself in the foot this way.
 
  Oops!  I'm sorry, I completely misread the proposal.  Or read it
 correctly,
  saw an undecidability hiding in there, and got carried away.
 
  What you are proposing is called equi-recursive types, in contrast to
 the
  more popular iso-recursive types (which Haskell uses).  There are
 plentiful
  undecidable problems with equi-recursive types, but there are ways to
 pull
  it off.  The question is whether these ways play nicely with Haskell's
 type
  system.
 
  But because of the fundamental computational problems associated, there
  needs to be a great deal of certainty that this is even possible before
  considering its language design implications.
 
 
  That inference engine seems to be a pretty little proof-of-concept,
  doesn't it?  But it is sweeping some very important stuff under the
 carpet.
 
  The proposal is to infer the type of a term,  then check it against an
  annotation.  Thus every program is well-typed, but it's the compiler's
 job
  to check that it has the type the user intended.  I like the idea

[Haskell-cafe] Timeout exceptions sometimes don't work, even in pure (non FFI) code

2011-02-01 Thread Job Vranish
I'm trying to test some properties with quickcheck. If these tests fail,
they will almost certainly fail by nontermination.
I've been using the 'within' function to catch these nontermination cases.
However, I was surprised to find that this doesn't always work.
'within' uses the 'timeout' function under the hood. Here is an example that
demonstrates the problem:

import System.Timeout
import Control.Exception

works :: Int - Int
works x = sum $ cycle [x]

doesntWork :: Int - Int
doesntWork x = last $ cycle [x]

test1 = timeout 1 $ evaluate $ works 5 == 5-- terminates
test2 = timeout 1 $ evaluate $ doesntWork 5 == 5   -- never terminates


test1 returns Nothing as expected, but test2 never terminates. Why?

I thought timeout exceptions are supposed to always work with pure (non FFI)
Haskell code.
Is there any way I can work around this?

I'm using ghc 6.12.2

Thanks,

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


Re: [Haskell-cafe] Timeout exceptions sometimes don't work, even in pure (non FFI) code

2011-02-01 Thread Job Vranish
Hmm, that's good to know.

It looks like it also works for most data dependency cases.

works = let
  a = b
  b = a
  in a

main = timeout 1 $ evaluate $ works

This terminates even with optimizations.

So I think I'll be able to work around it.
I wish timeout worked a little more consistently. This behavior is quite
annoying.

Thanks for your help,

- Job

On Tue, Feb 1, 2011 at 11:18 AM, Daniel Fischer 
daniel.is.fisc...@googlemail.com wrote:

 On Tuesday 01 February 2011 16:40:43, Job Vranish wrote:
  I'm trying to test some properties with quickcheck. If these tests fail,
  they will almost certainly fail by nontermination.
  I've been using the 'within' function to catch these nontermination
  cases. However, I was surprised to find that this doesn't always work.
  'within' uses the 'timeout' function under the hood. Here is an example
  that demonstrates the problem:
 
  import System.Timeout
  import Control.Exception
 
  works :: Int - Int
  works x = sum $ cycle [x]
 
  doesntWork :: Int - Int
  doesntWork x = last $ cycle [x]
 
  test1 = timeout 1 $ evaluate $ works 5 == 5-- terminates
  test2 = timeout 1 $ evaluate $ doesntWork 5 == 5   -- never terminates
 
 
  test1 returns Nothing as expected, but test2 never terminates. Why?

 When compiled with optimisations, works doesn't terminate either.

 I believe it's because works actually does some work and allocations
 (without optimisations), while doesntWork is a non-allocating loop.
 GHC only makes context switches on allocations, so with a non-allocating
 loop, the timeout thread never gets to run to see whether the time limit is
 exceeded.
 Without optimisations, sum allocates thunks, with optimisations it becomes
 a tight loop not hitting the heap. `last $ cycle [x]' becomes a tight loop
 even without optimisations.

 
  I thought timeout exceptions are supposed to always work with pure (non
  FFI) Haskell code.
  Is there any way I can work around this?

 Make sure your tests always allocate, or write them as IO stuff and call
 yield (or threadDelay) within the loops to let GHC make some context
 switches.

 
  I'm using ghc 6.12.2
 
  Thanks,
 
  - Job


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


Re: [Haskell-cafe] REPL loop

2010-12-20 Thread Job Vranish
The answer is yes, but could you elaborate? What exactly are you wanting? Do
you want something similar to ghci? Are you wanting to implement a REPL for
some other language in haskell? REPL for haskell, in haskell?

- Job

On Mon, Dec 20, 2010 at 12:47 PM, Aaron Gray aaronngray.li...@gmail.comwrote:

 Is it possible to implement a REPL (Read-eval-print loop) in Haskell ?

 Many thanks in advance,

 Aaron


 ___
 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] Couple of questions about *let* within *do*

2010-08-10 Thread Job Vranish
Yes, and yes :)

For example:

import Data.Char

main = do
  let prompt s = do
  putStrLn s
  getLine
  firstName - prompt What's your first name?
  lastName - prompt What's your last name?
  let bigFirstName = map toUpper firstName
  bigLastName = map toUpper lastName
  putStrLn $ hey  ++ bigFirstName ++   ++ bigLastName ++ , how are
you?

- Job

On Tue, Aug 10, 2010 at 12:40 PM, michael rice nowg...@yahoo.com wrote:


 From: Learn You a Haskell

 ===

 Remember let bindings? If you don't, refresh your memory on them by reading
 this section. They have to be in the form of let bindings in expression,
 where bindings are names to be given to expressions and expression is the
 expression that is to be evaluated that sees them. We also said that in list
 comprehensions, the in part isn't needed. Well, you can use them in do
 blocks pretty much like you use them in list comprehensions. Check this out:


   import Data.Char

 main = do
   putStrLn What's your first name?
   firstName - getLine
   putStrLn What's your last name?
   lastName - getLine
   let bigFirstName = map toUpper firstName
   bigLastName = map toUpper lastName
   putStrLn $ hey  ++ bigFirstName ++   ++ bigLastName ++ , how are
 you?

 ===

 Questions:

 1) Is there an implicit *in* before the last line above?

 2) Within a do in the IO monad (or any other monad), can a *let* do
 something like this?

   let x = do   -- in a different monad


 Michael



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


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


Re: [Haskell-cafe] More Flexible Monad Transformer OR Bad Coding Style

2010-08-09 Thread Job Vranish
For monads like StateT, WriterT, ReaderT, the order doesn't matter (except
perhaps for some pesky performance details). However, for monad transformers
like ErrorT or ListT, the order _does_ matter.

The code you have there is perfectly fine, sometimes the added generality
can be quite handy (especially if you have your own MonadState'esk type
classes).
The two major drawbacks to this approach (that I can think of off the top of
my head) are:
1) Rather large and complicated contexts on quite a few of your functions
2) Can lead to nearly indecypherable error messages

Personally, I try to avoid multiparameter typeclasses whenever possible;
I've found them to be more trouble than they are worth.

My advice would be to leave the code general if the code actually does
something general (it actually has more than one use case) and give the code
a fixed signature if the code really one has just one purpose (even if ghci
can infer a general type for you).
This is just a personal preference, but it seems to work well for me :)

- Job


On Mon, Aug 9, 2010 at 3:05 PM, aditya siram aditya.si...@gmail.com wrote:

 Hi all,
 I was experimenting with monad transformers and realized that the stacking
 order of the monads can remain unknown until it is used. Take for example
 the following code:

 import mtl Control.Monad.State
 import mtl Control.Monad.Writer
 import mtl Control.Monad.Identity

 test :: (MonadWriter [Char] m, Num t, MonadState t m) = m ()
 test = do
  put 1
  tell hello

 main = do
  x - return $ runIdentity $ runStateT (runWriterT test) 1 -- test ::
 WriterT String (StateT Int Identity)
  y - return $ runIdentity $ runWriterT $ runStateT test 1 -- test ::
 StateT Int (WriterT String Identity)
  z - runWriterT $ runStateT test 1-- test ::
 StateT Int (WriterT String IO) (((), Int), String)
  print x
  print y
  print z

 *Main main
 (((),hello),1)
 (((),1),hello)
 (((),1),hello)

 Until test is called in 'main' we don't know the order of monads. In fact
 even the base monad is not know. All we know is that it uses the State and
 Writer monad. In each call to 'test' in main we can determine the stacking
 order and the base monad yielding different results. This seems to be a more
 flexible way of using monad transformers but I haven't seen this in code
 before so is there anything wrong with this style?

 -deech

 ___
 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] real-time audio processing [Was: can Haskell do everyting as we want?]

2010-08-05 Thread Job Vranish
Yeah Atom is pretty slick, though unfortunately it's not quite powerful
enough for much of the stuff that we do.

John Van Enk and I are actually working on a language that's similar to C
(and compiles to C), but has polymorphism, type inference and other goodies.
The goal is to make working on embedded systems a bit less painful, while
still being able to do anything that C can do (like run on an 8 bit micro).
Hopfully, if things go as planned, we'll have a working beta out by the end
of the month :)

- Job

On Wed, Aug 4, 2010 at 5:58 PM, Don Stewart d...@galois.com wrote:

 job.vranish:
  + 1
 
 
  This is probably the biggest obstacle to using Haskell where I work.
 (Aviation
  industry, software for flight management systems for airplanes)
 
  We often need to perform some computations with hard deadlines, say every
 20ms,
  with very little jitter.
  Major GC's spoil the fun; It's quite easy to have a major GC take longer
 than
  20ms, and currently they are not pauseable (nor is it trivial to make
 them
  so).
 
  It would be very nice to have some annotation/DSL/compiler-flag that
 would let
  me run a small block of mostly regular haskell code under hard, real-time
  constraints.
 
  Hmm, it looks like the HASP project is working on some of this, though
 I'm not
  sure how portable their work is back to GHC: http://hasp.cs.pdx.edu/
 

 Or look at EDSLs, like Atom:

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

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


Re: [Haskell-cafe] ANNOUNCE: DSTM 0.1.1

2010-08-04 Thread Job Vranish
Both Git and GitHub are fantastic. (and very convenient for contributors)

Also if you're the kind of person who's into GUI's, SmartGit is quite good
as well.

- Job

On Wed, Aug 4, 2010 at 3:28 PM, Frank Kupke f...@informatik.uni-kiel.dewrote:

 John,

 a very nice idea. I have not worked with git yet but used an svn repository
 on our institute server. I will look into it though and eventually set
 something up. In the meantime you are welcome to send patches to me for
 merging them into the project.

 Frank

 Am 04.08.2010 um 18:54 schrieb John Van Enk:

 Is there a Git/Darcs dev repo hiding anywhere we could submit patches to?

 On Tue, Aug 3, 2010 at 4:35 AM, Frank Kupke 
 f...@informatik.uni-kiel.dewrote:

 Hi,

 DSTM is an implementation of a robust distributed Software Transactional 
 Memory (STM) library for Haskell. Many real-life applications are 
 distributed by nature. Concurrent applications may profit from robustness 
 added by re-implementation as distributed applications. DSTM extends the STM 
 abstraction to distributed systems and presents an implementation efficient 
 enough to be used in soft real-time applications. Further, the implemented 
 library is robust in itself, offering the application developer a high 
 abstraction level to realize robustness, hence, significantly simplifying 
 this, in general, complex task.

 The DSTM package consists of the DSTM library, a name server application, 
 and three sample distributed programs using the library. Provided are a 
 simple Dining Philosophers, a Chat, and a soft real-time Bomberman game 
 application. Distributed communication is transparent to the application 
 programmer. The application designer uses a very simple name server 
 mechanism to set up the system. The DSTM library includes the management of 
 unavailable process nodes and provides the application with abstract error 
 information thus facilitating the implementation of robust distributed 
 application programs.

 For usage please look into the documentation file: DSTMManual.pdf.

 The package including the documentation can be found 
 on:http://hackage.haskell.org/package/DSTM-0.1.1


 Best regards,
 Frank Kupke



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




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


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


Re: [Haskell-cafe] real-time audio processing [Was: can Haskell do everyting as we want?]

2010-08-04 Thread Job Vranish
+ 1


This is probably the biggest obstacle to using Haskell where I work.
(Aviation industry, software for flight management systems for airplanes)

We often need to perform some computations with hard deadlines, say every
20ms, with very little jitter.
Major GC's spoil the fun; It's quite easy to have a major GC take longer
than 20ms, and currently they are not pauseable (nor is it trivial to make
them so).

It would be very nice to have some annotation/DSL/compiler-flag that would
let me run a small block of mostly regular haskell code under hard,
real-time constraints.

Hmm, it looks like the HASP project is working on some of this, though I'm
not sure how portable their work is back to GHC: http://hasp.cs.pdx.edu/

- Job


On Wed, Aug 4, 2010 at 4:24 PM, Stephen Sinclair radars...@gmail.comwrote:

 On Aug 3, 8:31 pm, Jeremy Shaw jer...@n-heptane.com wrote:
   The only area I have had any trouble with Haskell is doing realtime
  music synthesis. And only because the garbage collector is not
  realtime friendly. That is not unfixable though. However, I am
  thinking that the best way to do realtime synthesis with Haskell is to
  use it to create a DSL that uses LLVM to create code at runtime so
  that the realtime code is outside the scope of the normal RTS and
  garbage collector.

 I'm also very interested in this topic---how to apply a general-
 purpose functional language to real-time needs, even if it is in a
 domain-specific way.

 Indeed, it mostly comes down to memory management and the fact that
 functional concepts like closures and laziness require a lot of
 dynamic allocation and garbage collection.  Certainly, one solution is
 to provide a real-time-friendly memory manager.

 However, it's interesting to notice that, as proven by FAUST [1], a
 huge amount of DSP algorithms can be expressed functionally in a real-
 time-compatible way by describing them as static diagrams of connected
 blocks.  These can be efficiently compiled to imperative code with no
 dynamic memory allocation required.

 So yes, if such a language were available as an embedded DSL in
 Haskell (one effort can be found here [2]), it could be generated at
 run-time using LLVM and called out to.  Alternatively, it would be
 very cool if it were possible to generate code statically at compile
 time, just like in FAUST.  I can imagine this being very useful,
 especially if it could be generalized to operate on datatypes other
 than floating points, and had easy access to data structures provided
 by non-RT portions of the code.  If there are mutability requirements,
 it could be made to run in the ST monad with a pre-allocated
 workspace.

 Of course _modifying_ such structures at run-time is always a dynamic
 thing by definition, although there is the possibility of dynamically
 generating a replacement block diagram while an one existing one runs,
 and using an atomic pointer swap to switch them without causing
 interruptions.

 In any case, as far as I know the only thing in the way is that it's
 impossible to tell GHC to compile a section of code in such as way as
 to guarantee avoidance of memory management.  Compilers and runtime-
 systems always seem to be either RT- or non-RT-friendly, but never
 seem to support the idea of code *portions* that have differing
 requirements.  My point is, RT code _can_ be expressed functionally,
 even if the RT-ness imposes certain expressivity restrictions.  It
 would be very cool to be able to mark sections of code as following
 such a sub-language and be guaranteed that the compiler will
 generate GC-free code for a particular function, if possible, or
 otherwise fail.

 Even if such a sub-language were no more expressive than C, it would
 be nice to be able to write it in Haskell instead of dropping down to
 C, so that data can be easily shared with non-RT parts, and Haskell's
 type checker could be exploited.  It seems strange to me that with
 technology like Haskell and GHC we still depend on using C to express
 these last remaining droplets of real-time determinism requirements---
 strange, since I think of higher-level languages like Haskell to be
 supersets of the capabilities of C---and annoying, because it means
 having to deal with the complexities of language interoperability,
 just for a few low-level components of an application.

 I realize some of this has probably been discussed in conjunction with
 FRP.  I'm aware of one paper on RT-FRP that talks about requiring an
 RT-friendly sub-language [3], but I don't pretend to follow it
 completely.  I'm almost sure it also has something to do with arrows,
 but I have very little idea what they are, since I'm still just
 getting monads at this point in my personal Haskell understanding.
 I hope someone more knowledgeable about these things on this list
 might be able to comment on their relation to real-time determinism.

 [1] http://faust.grame.fr/
 [2]
 

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

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

- Job

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

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

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

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

 -Eitan

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


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


Re: [Haskell-cafe] [Yi Editor]Cabal Problem

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

- Job

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

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

 -

 Im on windows, using Cabal in Cygwin.

 How should i install those missing libs?

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


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


Re: [Haskell-cafe] Problem with haskell types

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

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

However,

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

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


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

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

- Job

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

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

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

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

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

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

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

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


 On Sat, 31 Jul 2010, Anupam Jain wrote:

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

 Here's the program that refuses to compile -

 module Delme () where

 data DecisionState = A | B | C | D

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

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

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

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

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

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

 -- Anupam




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

Re: [Haskell-cafe] Memory and Threads - MVars or TVars

2010-07-29 Thread Job Vranish
You might try pulling downloading the package ('cabal fetch org'  will do
this) and changing the base dependency (to = 4.1) in the orc.cabal file and
then build it manually (cabal configure  cabal build  cabal install
(while in the same directory as the .cabal file)) and see what happens.

I don't see any obvious reasons why it would need a version greater than
6.10, so it might just be an over restrictive dependency rule, but I might
be missing something.

- Job

On Wed, Jul 28, 2010 at 10:49 PM, Eitan Goldshtrom
thesource...@gmail.comwrote:

 Ah! That clears that up a lot. I read the wiki page but something just
 didn't make full sense about it until you used the word prevent. I
 understand that the computer doesn't actually prevent other threads from
 running -- that would defeat the purpose of the concurrency -- but it helped
 clear it up. Perhaps you guys could help me with Cabal now though? I'm
 trying to install Orc but it wants base=4.2 and =4.3 and I have 4.1 after
 installing the latest release of GHC. Cabal won't upgrade the base. It
 complains about a dependency to integer-simple. Anyone know what that's
 about?


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

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


Re: [Haskell-cafe] OpenGL Speed!

2010-07-29 Thread Job Vranish
Yeah, using openGL Points to draw 2D images will probably be pretty slow.
However, if you don't need to change your points every frame, a display list
might improve the speed quite a bit (you could still transform the points as
a whole).

Also, you could try the SDL bindings for haskell:
http://hackage.haskell.org/package/SDL
SDL is better suited for 2D drawing (IMHO).
http://www.libsdl.org/


- Job


On Thu, Jul 29, 2010 at 6:51 AM, Vo Minh Thu not...@gmail.com wrote:

 2010/7/29 Eitan Goldshtrom thesource...@gmail.com:
  I'm having an unusual problem with OpenGL. To be honest I probably
 shouldn't
  be using OpenGL for this, as I'm just doing 2D and only drawing Points,
 but
  I don't know about any other display packages, so I'm making due. If this
 is
  a problem because of OpenGL however, then I'll have to learn another
  package. The problem is speed. I have a list of points representing the
  color of 800x600 pixels. All I'm trying to do is display the pixels on
 the
  screen. I use the following:
 
  renderPrimitive Points $ mapM_ display list
  flush
  where
display [] = return ()
display ((x,y,i):n) = do
  color $ Color3 i i i
  vertex $ Vertex2 x y
  display n
 
  But, for some reason this takes FOREVER. I don't know how to use
 debugging
  hooks yet without an IDE -- and I don't use an IDE -- but I used a
 cleverly
  placed putStrLn to see that it was actually working, just really really
  slowly. Is there a solution to this speed problem or should I use a
 package
  that's more suited to 2D applications like this? Also, if I should use
  another package, are there any suggestions for which to use? Thanks for
 any
  help.

 Hi,

 Although you can use Vertex* to put a single Point on the screen, it
 is not meant to be used as some kind of setPixel function.

 If your goal is simply to set pixels' value of a raster, you can still
 use OpenGL but should use a single textured quad (and thus manipulate
 the texture's pixels).

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

 HTH,
 Thu
 ___
 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] Memory and Threads - MVars or TVars

2010-07-28 Thread Job Vranish
Atomic operations are special operations where you don't have to worry about
some other process messing with things while the operation is taking place.

For a simple example of why atomic operations are important:
(taken from: http://en.wikipedia.org/wiki/Linearizability#Non-atomic)

The naive, non-atomic implementation:

   1. reads the value in the memory location;
   2. adds one to the value;
   3. writes the new value back into the memory location.

Now, imagine two processes are running incrementing a single, shared memory
location:

   1. the first process reads the value in memory location;
   2. the first process adds one to the value;

but before it can write the new value back to the memory location it is
suspended, and the second process is allowed to run:

   1. the second process reads the value in memory location, the *same* value
   that the first process read;
   2. the second process adds one to the value;
   3. the second process writes the new value into the memory location.

The second process is suspended and the first process allowed to run again:

   1. the first process writes a now-wrong value into the memory location,
   unaware that the other process has already updated the value in the memory
   location.


Atomic operations fix this problem by preventing (STM is a little fancier
and doesn't actually _prevent_, but you can pretend that it does) any other
process from writing to the memory in question until the computation is
finished and the result is written back.


For many simple cases something like atomicModifyIORef is all you really
need. However, if you have cases where you need to make sure _multiple_
IORefs/MVars/TVars/etc.. are not written to until you're finished then you
really need something like STMs 'atomically' function. Which runs a block of
STM operations atomically.

http://en.wikipedia.org/wiki/Linearizability#Non-atomicHope that helps,

- Job

On Wed, Jul 28, 2010 at 8:23 PM, Eitan Goldshtrom thesource...@gmail.comwrote:

  Hi everyone. I was wondering if someone could just guide me toward some
 good information, but if anyone wants to help with a personal explanation I
 welcome it. I'm trying to write a threaded program and I'm not sure how to
 manage my memory. I read up on MVars and they make a lot of sense. My real
 question is what is atomic and how does it apply to TVars? I don't
 understand what atomic transactions are and I can't seem to find a concise
 explanation. I also saw some stuff about TMVars? But I can't find much on
 them either. Any help would be appreciated.

 -Eitan

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


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


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

2010-07-26 Thread Job Vranish
I think most of the Erlang style actors with message passing can be done in
Haskell with just TChan and forkIO.

http://en.wikibooks.org/wiki/Haskell/Concurrency

- Job

On Sun, Jul 25, 2010 at 4:55 PM, Yves Parès limestr...@gmail.com wrote:

 Hello !

 I've been studying Erlang and Scala, and I was wondering if someone has
 already implemented an actors and message passing framework for concurrent
 and distributed programs in Haskell.

 ___
 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] Haskell Forum

2010-07-26 Thread Job Vranish
I agree. A web forum would be more friendly to newcomers, easier to browse,
and better organized, than the mailing list.

Some people will still prefer the mailing list of course, but I think there
will be enough demand to justify a forum :)

- Job



On Mon, Jul 26, 2010 at 9:57 AM, Daniel Díaz lazy.dd...@gmail.com wrote:

 Well, I thought that it may be a more comfortable way to communicate
 between us. Specially for newcomers. Don't forget that Haskell is a growing
 community.

 It's just my opinion.

 ___
 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] Yet another monad transformer or silly usage of Either?

2010-07-25 Thread Job Vranish
Yeah, ErrorT should do what you want (EitherT is probably essentially the
same thing)

login would have the type:
login :: String - String - ErrorT DServError IO LoginResponse

and you would use it like this:
result - runErrorT $ authenticatedReq

You can use runErrorT, or catch when you want to process a possible error.

result would have the type Either DServError whatever. This would leave out
the Result type, but if you really want to, you can add it with the
appropriate lifting.

Hope that helps,

- Job


2010/7/25 Eugeny N Dzhurinsky b...@redwerk.com

 Hello, everybody!

 I am trying to develop some sort of library, which supposed to sign into a
 WEB
 service, then perform some requests with it.

 Initially I designed methods in the following way

 data DServError = InvalidCredentials | InvalidRequest | ...

 newtype Result a = Result { getOpResult :: Either DServError a }

 data DSession = Session { ... }

 data DLoginResponse = LoginResponse { currentSession :: DSession, ... }

 login :: String - String - IO ( Result LoginResponse )

 servRequest1 :: DSession - ParamType1 - ParamType2 - ... - IO ( Result
 DServResponse )


 Now I want to be able of doing something like

 authenticatedReq = do
loginResponse - login username password
let session = currentSession loginResponse
servRequest1 session ... ... ...
servRequest2 session ... ... ...
...

 so if login succeeds - I will be able to extract Right data from the Either
 response ( with
 explicit or implicit usage of getOpResult), if any of operations within
 do
 block will fail with DServError - then an error should be reported.

 I think the solution for this may be using Control.Exception and it's
 try/catch? Or may be there's some trick available for Either?

 I looked at EitherT, and it seems that I have to wrap every invocation into
 EitherT and then chain them with /=

 --
 Eugene Dzhurinsky

 ___
 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] Tiger compiler in Haskell: annotating abstract syntax tree

2010-07-19 Thread Job Vranish
Martijn van Steenbergen has a good blog post that describes the method I
generally use:
http://martijn.van.steenbergen.nl/journal/2010/06/24/generically-adding-position-information-to-a-datatype/

In his example he annotates the expression tree with position information,
but you can use the same method to add type annotations, or whatever you
want.

- Job


2010/7/19 José Romildo Malaquias j.romi...@gmail.com

 Hello.

 In his book Modern Compilder Implementation in ML, Appel presents a
 compiler project for the Tiger programming language where type checking
 and intermediate code generation are intrinsically coupled.

 There is a function

  transExp :: Absyn.Exp - (Tree.Exp,Types.Type)

 that do semantic analysis, translating an expression to the Tree
 intermediate representation language and also do type checking,
 calculating the type of the expression.

 Maybe the compiler can be made more didatic if these phases are separate
 phases of compilation.

 The type checker would annotate the abstract syntax tree (ast) with type
 annotations, that could be used later by the translater to intermediate
 representation.

 In an imperative language probably each relevant ast node would have a
 field for the type annotation, and the type checker would assign the
 type of the node to this field after computing it.

 I am writing here to ask suggestions on how to annotate an ast with
 types (or any other information that would be relevant in a compiler
 phase) in Haskell.

 As an example, consider the simplified ast types:

  data Exp
= IntExp Integer
| VarExp Symbol
| AssignExp Symbol Exp
| IfExp Exp Exp (Maybe Exp)
| CallExp Symbol [Exp]
| LetExp [Dec] Exp

  data Dec
 = TypeDec Symbol Ty
 | FunctionDec Symbol [(Symbol,Symbol)] (Mybe Symbol) Exp
 | VarDec Symbol (Maybe Symbol) Exp

 Expressions can have type annotations, but declarations can not.

 Comments?


 Regards,

 Romildo
 --
 Computer Science Department
 Universidade Federal de Ouro Preto, Brasil
 ___
 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] qtHaskell

2010-07-19 Thread Job Vranish
I haven't used the Gtk bindings much, but the qtHaskell bindings work quite
well. If you've used Qt before, it should be pretty easy to pick up.

- Job

On Mon, Jul 19, 2010 at 10:19 AM, Ali Razavi ali.raz...@gmail.com wrote:

 Greetings,
  I have only used the wxHaskell library before, but I am looking into
 trying one of these more 'advanced' frameworks. To serve my proclivity for
 QT, I would like to know how its Haskell binding, qtHaskell, compares to
 that of Gtk.

 Regards,
 Ali Razavi



 ___
 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] Tiger compiler in Haskell: annotating abstract syntax tree

2010-07-19 Thread Job Vranish
Ah, I found the attachment on your other email.

I would recommend using the Fix and Ann types, instead of the AnnFix type.

I modified your code a bit (and fixed the Show instances etc...) and put it
here:
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=27823#a27823

Let me know if you have questions about it.

- Job
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=27823#a27823

2010/7/19 Job Vranish job.vran...@gmail.com

 I didn't get any attachments from you, but haskell-cafe might filter them
 out (I'm not sure).

 But, the usual derived instances for Show should work fine for your
 expression and annotation types.
 For the Fix type you can use:

 instance (Show (f (Fix f))) = Show (Fix f) where
   show (Fix a) = show Fix  ++ show a

 hmmm, but you'll probably need:

 {-# LANGUAGE FlexibleContexts, UndecidableInstances #-}


 - Job



 2010/7/19 José Romildo Malaquias j.romi...@gmail.com

 On Mon, Jul 19, 2010 at 01:51:57PM -0400, Job Vranish wrote:
  Martijn van Steenbergen has a good blog post that describes the method I
  generally use:
 
 http://martijn.van.steenbergen.nl/journal/2010/06/24/generically-adding-position-information-to-a-datatype/
 
  In his example he annotates the expression tree with position
 information,
  but you can use the same method to add type annotations, or whatever you
  want.

 After a quick read at Martijn blog article I've written the attached
 test program, which works.

 But I am not succeeding in deriving Show for the data types. Any help?

 Romildo

  2010/7/19 José Romildo Malaquias j.romi...@gmail.com
 
   Hello.
  
   In his book Modern Compilder Implementation in ML, Appel presents a
   compiler project for the Tiger programming language where type
 checking
   and intermediate code generation are intrinsically coupled.
  
   There is a function
  
transExp :: Absyn.Exp - (Tree.Exp,Types.Type)
  
   that do semantic analysis, translating an expression to the Tree
   intermediate representation language and also do type checking,
   calculating the type of the expression.
  
   Maybe the compiler can be made more didatic if these phases are
 separate
   phases of compilation.
  
   The type checker would annotate the abstract syntax tree (ast) with
 type
   annotations, that could be used later by the translater to
 intermediate
   representation.
  
   In an imperative language probably each relevant ast node would have a
   field for the type annotation, and the type checker would assign the
   type of the node to this field after computing it.
  
   I am writing here to ask suggestions on how to annotate an ast with
   types (or any other information that would be relevant in a compiler
   phase) in Haskell.
  
   As an example, consider the simplified ast types:
  
data Exp
  = IntExp Integer
  | VarExp Symbol
  | AssignExp Symbol Exp
  | IfExp Exp Exp (Maybe Exp)
  | CallExp Symbol [Exp]
  | LetExp [Dec] Exp
  
data Dec
   = TypeDec Symbol Ty
   | FunctionDec Symbol [(Symbol,Symbol)] (Mybe Symbol) Exp
   | VarDec Symbol (Maybe Symbol) Exp
  
   Expressions can have type annotations, but declarations can not.
  
   Comments?



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


Re: [Haskell-cafe] use of modules to save typing

2010-07-08 Thread Job Vranish
For working with record fields inside of state monads I would recommend
trying out one of these packages:
lenses
fclabels
data-accessor
(I think I'm forgetting a couple)

They all have special mechanisms for working with record fields inside state
monads (and have lots of other cool stuff)
I'm partial to lenses (I wrote it :) ), but the others are quite good as
well.

Hmmm I just noticed that hackage is not generating the documentation for
latest version of lenses. I shall have to find out why.
In the meantime, the documentation for the 0.1.2 version is essentially the
same.

- Job


On Thu, Jul 8, 2010 at 4:08 AM, Michael Mossey m...@alumni.caltech.eduwrote:

 I'm fairly beginnerish to Haskell, and come from OO. I have a complaint
 about Haskell, but I think I found a good solution. Any suggestions welcome.

 I have RSI and like to minimize typing. The use of classes as name spaces
 helps to do that. Also I can use some Emacs abbreviation magic easily with
 OO and not so easily with Haskell. I'll explain in a second.

 In Haskell, when defining data for complex programs I like to use named
 fields to allow for changing data definitions without having to change all
 code. But named fields are top-level functions (I think). They must be
 chosen not to clash.

 My habit has been to prefix them with the name of the constructor. So in a
 program for playing back musical documents that needs to track some state,
 we have:

 data PlayState = PlayState
 { playState_cursor :: Int
 , playState_verts :: [Loc]
 , playState_len :: Int
 , playState_doc :: MusDoc
 }

 Note all these playState_ prefixes. Lots of typing, which is not good.

 In OO, you could type

   x.cursor()

 In Haskell you have to type

   playState_cursor x

 which also, I feel, is harder to read.

 Now suppose I want to use PlayState with a State monad.

 -- Increment the cursor.
 incrCursor :: State PlayState ()
 incrCursor =
  cur - gets playState_cursor
  len - gets playState_len
  let newCur = min (cur+1) (len-1)
  p - get
  put $ p {playState_cursor = newCur}

 Okay, I'm sorry, that is just a lot of typing for what it is doing. Not
 good for people with RSI, and not all that readable.

 I could define a function to make modifying the state a little easier.

 playState_update_cursor :: Int - PlayState - PlayState
 playState_update_cursor i p = p {playState_cur=i}

 Then incrCursor would look like:

 incrCursor :: State PlayState ()
 incrCursor =
  cur - gets playState_cursor
  len - gets playState_len
  let newCur = min (cur+1) (len-1)
  modify (playState_update_cursor newCur)

 Notice how often the characters playState_ get typed. This would be a
 great situation for Emacs abbreviations. When you define an abbreviation in
 Emacs, such as defining xps to expand to PlayState, emacs will watch for
 the characters xps. It will then replace xps with PlayState when you
 type a non-alphanumeric character following xps. So if I type xps. the
 moment I hit . it changes to PlayState.

 But I would have a hard time using this feature with playState_ because
 it is always followed by an alphanumeric character.

 So my idea, now, is to put the definition of PlayState in its own module
 and import it qualified as PlayState.

  module PlayState --

 data PlayState = PlayState
   { cursor :: Int
   , verts :: [Loc]
   , len :: [Int]
   , doc :: MusDoc
   }

 update_cursor i p = p {cursor = i}

 ---

 I got rid of the playState_ prefixes because I am not worried about using
 generic field names like doc. They won't clash if I always import this
 qualified. And that reduces the necessary typing in the definition.

 Now my monad looks like

 testMonad = do
  cursor - gets PlayState.cursor
  len- gets PlayState.len
  let newCur = min (cur+1) (len-1)
  modify $ PlayState.update_cursor newCur

 Now I can define an abbreviation for PlayState. This is a big help. Also, I
 find this more readable. To me

   PlayState.cursor

 is more readable than
   playState_cursor

 For one thing, syntax highlighting helps in the former case. For another,
 the latter case requires that you recognize a naming convention, but the
 former case says clearly: cursor is within the namespace PlayState, so this
 combination must be describing a cursor related to PlayState.





 ___
 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: Re: [Haskell-cafe] Criteria for determining if a recursive function can be implemented in constant memory

2010-07-06 Thread Job Vranish
If your integers have a bounded size, then your Turing machine is not Turing
complete and can't run a Haskell interpreter.

You might be tempted to just make the numbers really big, but bounded, and
then say that you can still run most interesting programs while skirting the
issue of non computability.  But you will find that all the problems that
are now theoretically solvable are still computationally intractable, and
you are practically back where you started.

This doesn't mean that you can't make programs that can determine very
interesting non-trivial properties of programs/functions, but it does mean
that there is no way to make them always work.

- Job


On Tue, Jul 6, 2010 at 9:37 AM, Steffen Schuldenzucker 
sschuldenzuc...@uni-bonn.de wrote:


 Forwarding this message to the list.

 No, I didn't think about the size of integers. For now, let all numbers
 have some bounded size.


  Original Message   Subject: Re: [Haskell-cafe] Criteria
 for determining if a recursive function can be implemented in constant
 memory  Date: Tue, 6 Jul 2010 13:25:57 +1200  From: Richard O'Keefe
 o...@cs.otago.ac.nz o...@cs.otago.ac.nz  To: Steffen Schuldenzucker
 sschuldenzuc...@uni-bonn.de sschuldenzuc...@uni-bonn.de

 On Jul 6, 2010, at 12:23 AM, Steffen Schuldenzucker wrote:
  Given the definition of a recursive function f in, say, haskell,
  determine if f can be implemented in O(1) memory.

 How are you supposed to handle integer arithmetic?

 If you don't take the size of integers into account,
 then since a Turing machine can do any computation,
 it can run a Haskell interpreter, and since a Turing
 machine's tape can be modelled by a single integer
 (or more conveniently by two), any Haskell function
 can be implemented in O(1) Integers.

 If you do take the size of integers into account,
 then
 pow2 n = loop n 1
   where loop 0 a = a
 loop (m+1) a = loop m (a+a)
 requires O(n) memory.


 ___
 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] Inferring the most general type

2010-06-22 Thread Job Vranish
Esteemed fellow haskellers,

I recently ran into a very simple real life case where Haskell's rules for
inferring the types for mutually recursive definitions resulted in a type
that was less general than it could be. It took me a while to realize that
the type error I was getting wasn't actually a problem with my code. I
understand why Haskell does this (it infers the strongly connected mutually
recursive definitions monomorphically), but I think it _could_ infer the
more general type even with recursive definitions like this.

Here is a simplified example that illustrates the problem:

 import Data.Maybe

 -- The fixed point datatype
 data Y f = Y (f (Y f))

 -- silly dummy function
 maybeToInt :: Maybe a - Int
 maybeToInt = length . maybeToList

 -- f :: Y Maybe - Int
 f (Y x) = g maybeToInt x

 g h x = h $ fmap f x

This is the type it wants to infer for g
g :: (Maybe Int - Int) - Maybe (Y Maybe) - Int

This is the type I think it should have, note you can't force the type with
a typesig without -XRelaxedPolyRec
g :: (Functor f) = (f Int - b) - f (Y Maybe) - b

If I use -XRelaxedPolyRec I can manually specify the more general type, but
then I have to convince myself that there isn't a more general type that I'm
missing.


Are there other known algorithms that yield a more general type? and if so,
what was the rational for Haskell keeping the current method?

I worked out an alternative algorithm that would give a more general type
(perhaps the most general type) but it has factorial complexity and probably
wouldn't be good for strongly connected groups with 7 or more members.

Even so, I would much rather have the inferred types always be the most
general ones and be required to add type signatures for mutually recursive
groups with 7 or more members (which probably need to be redesigned anyway)
than be always required to manually figure out the more general signatures.
What do you think?


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


Re: [Haskell-cafe] How to browse code written by others

2010-06-14 Thread Job Vranish
I've been using the geany http://www.geany.org/ editor recently and I was
shocked to find that it has decent source browsing capabilities (that work
with haskell even!). You can find where something is defined and find other
usages of things. It's a bit crude, but gets the job done well enough.

- Job


On Sun, Jun 13, 2010 at 4:32 PM, Martin Drautzburg martin.drautzb...@web.de
 wrote:

 Hello all,

 I need your advice about how to browse code which was written by someone
 else
 (Paul Hudak's Euterpea, to be precise, apx. 1 LOC). I had set some
 hopes
 on leksah, and it indeed shows me the interfaces, but I have not yet
 convinced it to show me more than that.

 I ran haddock over the sources, and again I could not see more that just
 signatures.

 I would be very happy with something like a Smalltalk browser. Something
 that
 would let me zoom down to the source code, but with search and hyperlink
 capabilities (senders and implementers in Smalltalk).

 Anyways, how do you guys do it, i.e. how to you dive into non-trivial
 foreign
 code?


 --
 Martin
 ___
 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] Using the ContT monads for early exits of IO ?

2010-06-10 Thread Job Vranish
Yeah I don't see why not. The ContT monad should work great.
Also, depending on what you're doing, the ErrorT monad might do what you
want as well.

- Job

2010/6/10 Günther Schmidt gue.schm...@web.de

 Hi everyone,

 I'm about to write a rather lengthy piece of IO code. Depending on the
 results of some of the IO actions I'd like the computation to stop right
 there and then.

 Now I know in general how to write this but I'm wondering if this is one of
 those occasions where I should make use of the Cont monad to make an early
 exit.

 Günther

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

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


Re: [Haskell-cafe] Re: Using the ContT monads for early exits of IO ?

2010-06-10 Thread Job Vranish
Yeah, I might actually prefer calling it EitherT instead of ErrorT. It
doesn't have to be used for error, it's just what it is most often used for.

- Job

On Thu, Jun 10, 2010 at 3:57 PM, Maciej Piechotka uzytkown...@gmail.comwrote:

 On Thu, 2010-06-10 at 14:09 -0500, Tim Wawrzynczak wrote:
  Actually, on second thought, Lennart is probably right.  Continuations
  are probably overkill for this situation.
  Since not wanting to continue is probably an 'erroneous condition,'
  you may as well use Error.
 
  Cheers,
   - Tim
 

 Technically it can be a success. For example if we get a list of
 HostInfo for given hostname we want to connect once instead of many
 times. Also the first time might not succeed (it is  entry in IPv4
 network).

 Error monad seems not to be a semantic solution as we exit on success
 not failure.

 Regards



 ___
 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] Proposal to solve Haskell's MPTC dilemma

2010-06-08 Thread Job Vranish
Sorry for reopening an old thread, but I thought I'd counter some of the
negative feedback :)


I think this proposal is a great idea!

It seems like this would make working with MPTCs much easier.
When programming, I generally want to only specify the minimum amount of
information to make my code logically unambiguous.
If the code contains enough information to infer the proper instantiation
without the use of an FD, then I shouldn't need to add a FD.
It seems like this would have much more of a it just works feel than the
currently alternatives.

Also the MPTC + FDs type errors are a pain. I'm not sure if the type errors
for your proposal would be better, but it would be hard to make them worse.

I do worry about imported instances, (over which we currently have little
control) messing up our code. But this would probably be pretty unusual and
I feel that this is more of a problem with how instances are imported than
with this proposal itself.


Anyway, just my two cents,

- Job


On Thu, May 20, 2010 at 10:34 AM, Carlos Camarao
carlos.cama...@gmail.comwrote:

 This message presents, informally, a proposal to solve Haskell's MPTC
 (multi-parameter type class) dilemma. If this informal proposal turns
 out to be acceptable, we (I am a volunteer) can proceed and make a
 concrete proposal.

 The proposal has been published in the SBLP'2009 proceedings and is
 available at
 
 www.dcc.ufmg.br/~camarao/CT/solution-to-MPTC-dilemma.pdfhttp://www.dcc.ufmg.br/%7Ecamarao/CT/solution-to-MPTC-dilemma.pdf

 The well-known dilemma
 (hackage.haskell.org/trac/haskell-prime/wiki/MultiParamTypeClassesDilemma)
 is that it is generally accepted that MPTCs are very useful, but their
 introduction is thought to require the introduction also of FDs
 (Functional Dependencies) or another mechanism like ATs (Associated
 Types) and FDs are tricky and ATs, somewhat in a similar situation,
 have been defined more recently and there is less experience with its
 use.

 In

 www.haskell.org/ghc/dist/current/docs/html/users_guide/type-class-extensions.html
 there exists a solution to the termination problem related to the
 introduction of MPTCs in Haskell. In our proposal, neither FDs nor any
 other mechanism like ATs are needed in order to introduce MPTCs in
 Haskell; the only change we have to make is in the ambiguity
 rule. This is explained below. The termination problem is essentially
 ortogonal and can be dealt with, with minor changes, as described in
 the solution presented in the above mentioned (type-class-extensions)
 web page.

 Let us review the ambiguity rule used in Haskell-98 and after that the
 ambiguity rule used in GHC. Haskell-98 ambiguity rule (which is
 adequate for Haskell-98's single parameter type classes) is: a type
 C = T is ambiguous iff there is a type variable v that occurs in the
 context (constraint set) C but not in the simple (unconstrained)
 type T.

 For example: forall a.(Show a, Read a)=String is ambiguous, because
 a occurs in the constraints (Show a,Read a) but not in the simple
 type (String).

 In the context of MPTCs, this rule alone is not enough. Consider, for
 example (Example 1):

class F a b where f:: a-b
class O a where o:: a
 and
 k = f o:: (C a b,O a) = b

 Type forall a b. (C a b,O a) = b can be considered to be not
 ambiguos, since overloading resolution can be defined so that
 instantiation of b can determine that a should also be
 instantiated (as FD b|-a does), thus resolving the overloading.

 GHC, since at least version 6.8, makes significant progress towards a
 definition of ambiguity in the context of MPTCs; GHC 6.10.3 User’s
 Guide says (section 7.8.1.1):

   GHC imposes the following restrictions on the constraints in a type
   signature. Consider the type: forall tv1..tvn (c1, ...,cn) = type. ...
   Each universally quantified type variable tvi must be reachable from
 type.
   A type variable a is reachable if it appears in the same constraint as
   either a type variable free in the type, or another reachable type
 variable.”

 For example, type variable a in constraint (O a) in the example
 above is reachable, because it appears in (C a b) (the same constraint
 as type variable b, which occurs in the simple type).

 Our proposal is: consider unreachability not as indication of
 ambiguity but as a condition to trigger overloading resolution (in a
 similar way that FDs trigger overloading resolution): when there is at
 least one unreachable variable and overloading is found not to be
 resolved, then we have ambiguity. Overloading is resolved iff there is
 a unique substitution that can be used to specialize the constraint
 set to one, available in the current context, such that the
 specialized constraint does not contain unreachable type variables.
 (A formal definition, with full details, is in the cited SBLP'09 paper.)

 Consider, in Example 1, that we have a single instance of F and
 O, say:

 instance F Bool Bool where f = not
 instance O Bool where o = 

[Haskell-cafe] Good US Grad schools for functional languages?

2010-05-13 Thread Job Vranish
Anybody know of a good grad school in the US for functional languages?
(good = has Ph.D. program that covers functional languages, type systems,
correctness proofs, etc...)

So far Indiana University is the only one I've found that has a strong
showing in this area.

A way to get into one of the awesome UK schools for free would work too :D

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


Re: [Haskell-cafe] Good US Grad schools for functional languages?

2010-05-13 Thread Job Vranish
Thanks for the input.

I don't have problems with traveling. The two main obstacles with going to a
school in Europe are:
1. Cost
2. I only speak english

I would be more than willing to learn another language, but I would like to
start working towards a PhD in the next year or so, and I don't think I'd
have enough time.

- Job

On Thu, May 13, 2010 at 1:47 PM, Pierre-Etienne Meunier 
pierreetienne.meun...@gmail.com wrote:

 If you imperatively need to stay in the US, I do not know if there's even
 one. If you do not have problems with traveling, you can have a look at :

 http://mpri.master.univ-paris7.fr/

 Which gathers the best french students (from such schools as Ecole
 Polytechnique, ENS Ulm, ENS Cachan). Or I know else of people who did a
 Ph.D. in sweden with Thierry Coquand for instance. Per Martin-Löf is there
 too.


 Cheers,
 PE


 El 13/05/2010, a las 13:41, Job Vranish escribió:

  Anybody know of a good grad school in the US for functional languages?
  (good = has Ph.D. program that covers functional languages, type systems,
 correctness proofs, etc...)
 
  So far Indiana University is the only one I've found that has a strong
 showing in this area.
 
  A way to get into one of the awesome UK schools for free would work too
 :D
 
  - Job
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe


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


Re: [Haskell-cafe] Re: GSoC: Hackage 2.0

2010-04-09 Thread Job Vranish
I vote for adding a feature that would let people post comments/code
snippets to the documentation of other peoples packages :)

It would be even nicer if you could post comments to individual haskell
definitions on the haddock page, and then hide most of them by default under
an expander of some sort.

I've often spent time trying to figure out how poorly documented function(s)
on someone else's package worked. Once I've figured it out, I usually have a
nice little example or explanation that I could post to save other people
the same trouble. Having an easy way to do this would be nice.

Basically any collaborative/wikish enhancements to the documentation on
hackage packages would make me happy :)

- Job

On Wed, Apr 7, 2010 at 4:43 AM, Matthew Gruen wikigraceno...@gmail.comwrote:

 On Wed, Apr 7, 2010 at 12:40 AM, Matthew Gruen wikigraceno...@gmail.com
 wrote:
  Hi Haskellers,
 
  snip

 Oh, heh, I apologize if that was more of a wall of text than I had
 realized. The above wasn't a project proposal itself, more the result
 of some brainstorming and some research. If you have the time to read
 it, I'd really appreciate your feedback.

 In fewer words, what kinds of features would benefit the community
 most for Hackage?

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

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


Re: [Haskell-cafe] Re: GSoC: Hackage 2.0

2010-04-09 Thread Job Vranish
On Fri, Apr 9, 2010 at 9:46 AM, Ivan Lazar Miljenovic 
ivan.miljeno...@gmail.com wrote:

 Job Vranish job.vran...@gmail.com writes:
  I vote for adding a feature that would let people post comments/code
  snippets to the documentation of other peoples packages :)

 You mean turn every hackage project page into a mini wiki?

 Yep.


  It would be even nicer if you could post comments to individual haskell
  definitions on the haddock page, and then hide most of them by default
 under
  an expander of some sort.

 Rather than, you know, providing the maintainer with a patch with some
 improved documentation?


This is often more difficult than it sounds. The biggest obstacle to this
approach is that a new hackage version of the package must to be uploaded to
update the documentation and the authors (me included) tend to prefer to
push new packages only when there are significant changes.

Steps involved currently:
0. pull down package source to build manually
1. add documentation/code snippet to source
2. build haddock documentation
3. debug bad/ugly syntax / missing line breaks that break haddock
4. generate a patch
5. email patch to author
6. wait a week for the author to actually get around to applying the patch
to whatever repository the source resides
7. wait several weeks for the author to release the next version of the
package

Steps involved with mini wiki:
0. add [code] [/code] tags (or whatever)
1. copy
2. paste
3. submit

I think making this process easier would greatly increase the community
involvement in the generation of documentation and improve the quality of
the documentation as a whole.

I would imaging that this would not be a trivial task, but I think even
something super simple (like what they have for the php documentation) would
be much better than nothing.

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


Re: [Haskell-cafe] Re: GSoC: Hackage 2.0

2010-04-09 Thread Job Vranish
On Fri, Apr 9, 2010 at 10:31 AM, Edward Kmett ekm...@gmail.com wrote:

 On Fri, Apr 9, 2010 at 10:21 AM, Job Vranish job.vran...@gmail.comwrote:

 On Fri, Apr 9, 2010 at 9:46 AM, Ivan Lazar Miljenovic 
 ivan.miljeno...@gmail.com wrote:

 Job Vranish job.vran...@gmail.com writes:
  I vote for adding a feature that would let people post comments/code
  snippets to the documentation of other peoples packages :)
 You mean turn every hackage project page into a mini wiki?

 Yep.


 How would such annotations/snippets/changes react to the next release of
 the package? Would they be per-package? per version?

 -Edward Kmett


Yeah that's the sticky part.

I think I would make comments only apply only to the version of the package
they were submitted to, and then make it the package maintainers
responsibility to potentially update the hard documentation with the more
useful comments when he/she releases the next version.

This keeps the comments up to date, and helps prevent things from getting
too clogged up with junk comments.

It would also be nice to provide an easy way for maintainers to copy
comments from older versions to newer ones, but this is a bit more tricky to
implement.

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


Re: [Haskell-cafe] Re: GSoC: Hackage 2.0

2010-04-09 Thread Job Vranish
On Fri, Apr 9, 2010 at 10:46 AM, Malcolm Wallace 
malcolm.wall...@cs.york.ac.uk wrote:

  It would be even nicer if you could post comments to individual haskell
  definitions on the haddock page, and then hide most of them by default
 under
  an expander of some sort.

 Rather than, you know, providing the maintainer with a patch with some
 improved documentation?



 How much cooler it would be, if the wiki-like comment on Hackage could
 automatically be converted into a darcs/git/whatever patch, and mailed to
 the package author/maintainer by Hackage itself.

 This would indeed be awesome :)

Though I think I would prefer to select, from a list of comments, which ones
I would like to include, and then click the Download darcs/git/whatever
patch button. (rather than get hit by emails )

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


[Haskell-cafe] Why does Haskell not infer most general type?

2010-04-06 Thread Job Vranish
Is haskell supposed to always infer the most general type (barring
extensions)?

I found a simple case where this is not true:

f _ = undefined
  where
_ = y :: Int - Int

y x = undefined
  where
_ = f x

Haskell infers the types of 'y' and 'f' as:
f :: Int - a
y :: Int - Int

This confused me at first, but after thinking about it a while it seemed to
make sense. But then my friend John pointed out that you can add type sigs
for 'f' and 'y':
f :: a - b
y :: a - b
and have it still typecheck!

This thoroughly confused me.

Why does haskell not infer the most general type for these functions? Is it
a limitation of the algorithm? a limitation of the recursive let binding?

Any insight would be appreciated :)

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


Re: [Haskell-cafe] Why does Haskell not infer most general type?

2010-04-06 Thread Job Vranish
So in Haskell 98, would the added constraints result in a type error?

- Job

On Tue, Apr 6, 2010 at 5:12 PM, Ross Paterson r...@soi.city.ac.uk wrote:

 On Tue, Apr 06, 2010 at 03:56:32PM -0400, Job Vranish wrote:
  f _ = undefined
where
  _ = y :: Int - Int
 
  y x = undefined
where
  _ = f x

 Because f and y are mutually recursive, their types are inferred together,
 so y gets the type Int - Int (as given), which forces f :: Int - a.

 If you add the type signature f :: a - b, you break the cycle: that
 type is used in inferring the type of y (namely a - b), which is then
 used in checking the typeof f.  Ditto if you add y :: a - b instead.
 (This is not Haskell 98, but the implementations have done this for
 years, and it will be in Haskell 2010.)
 ___
 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] Why does Haskell not infer most general type?

2010-04-06 Thread Job Vranish
Thank you all for your replies. This is all much more clear now :)

- Job

On Tue, Apr 6, 2010 at 7:00 PM, Ross Paterson r...@soi.city.ac.uk wrote:

 On Tue, Apr 06, 2010 at 05:18:34PM -0400, Job Vranish wrote:
  So in Haskell 98, would the added constraints result in a type error?

 Yes, because the types of the mutually recursive identifiers would be
 inferred together without using the type signatures, and then would
 fail to match the declared types.

 But then there aren't any implementations of Haskell 98 to test this on.
 ___
 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] ANN: fixed-list -- A fixed length list library

2010-03-21 Thread Job Vranish
Is there anything wrong with increasing the context stack? That's what I do
when I run into an overflow, and so far I haven't had any problems with it.

Generally my uses of FixedList involve relatively short lists (vectors and
such) so it usually isn't a problem.

I could implement a more sophisticated way to keep track of the list lengths
that doesn't have this problem, but I really like the simplicity of the
current implementation.

- Job

On Sun, Mar 21, 2010 at 2:37 AM, Casey McCann syntaxgli...@gmail.comwrote:

 Job Vranish job.vran...@gmail.com wrote:
  Its main advantages are:
   Very easy to use.
   Almost entirely Haskell98 (the non Haskell98 pieces are not critical,
 just
  nice)
   The datatype is a member of  Foldable, Traverable, Applicative, Monad,
  etc...
   Then length of the list is encoded in the type in a natural way.

 Unfortunately, it's very easy to get a context reduction stack
 overflow from GHC this way, which makes using such datatypes awkward
 for anything but very short lists. Explicit type annotations will
 often make things work, but at that point the type class isn't helping
 you anyway. For example, assuming the default stack size:

 import Data.FixedList

 fixed18 :: FixedList18 Int
 fixed18 = fromFoldable' [1..] -- this works

 fixed20 = 20 :. 20 :. fixed18 -- this works

 fixed22 :: FixedList22 Int
 fixed22 = 22 :. 22 :. fixed20 -- this only works with a type annotation

 show18 = show fixed18 -- this works

 -- this doesn't work:
 -- show20 = show fixed20

 show20' :: FixedList20 Int - String
 show20' list20 = show list20

 show20 = show20' fixed20 -- this does work

 Using head and tail on longer lists fails likewise. I expect there's
 some way to make it work without simply increasing the stack depth,
 but I'm not sure how. Any thoughts?

 - C.

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


[Haskell-cafe] ANN: fixed-list -- A fixed length list library

2010-03-20 Thread Job Vranish
I uploaded a new fixed length list library to hackage:

http://hackage.haskell.org/package/fixed-list


Its main advantages are:
  Very easy to use.
  Almost entirely Haskell98 (the non Haskell98 pieces are not critical, just
nice)
  The datatype is a member of  Foldable, Traverable, Applicative, Monad,
etc...
  Then length of the list is encoded in the type in a natural way.


Comments/critiques/suggestions welcome :)

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


Re: [Haskell-cafe] Abstraction in data types

2010-03-18 Thread Job Vranish
A phantom type might do what you want:

-- notice the type parameter on point that isn't used in the type
data Point  a  = Cartesian (Cartesian_coord, Cartesian_coord)
 | Spherical (Latitude, Longitude)

-- make some dummy types
data SphericalP
data CartesianP

--make some constructors that add a restriction to the phantom type
-- notice the CartesianP type restriction, this isn't needed but allows us
to restrict our type later if we want
mkCartesian :: (Cartesian_coord, Cartesian_coord) - Point  CartesianP
mkCartesian = Cartesian

mkSherical :: (Latitude, Longitude) - Point  SphericalP
mkSherical = Spherical


type Center = Point
type Radius = Float

-- now the shape type doesn't care which type of point you have, but
requires that all the points are the same
data Shape  a = Circle Center Radius
   | Polygon [Point a]


The main problem here, is that you want to hide the Cartesian and Spherical
constructors and only use mkCartesian and mkSherical to make Points (so that
they have the proper restrictions). But this prevents you from using pattern
matching where you have the constructors hidden.

GADTs however will solve that:

data Point a where
  Cartesian :: (Cartesian_coord, Cartesian_coord) - Point CartesianP
  Spherical :: (Latitude, Longitude)- Point SphericalP

Hope that helps :)

- Job

On Thu, Mar 18, 2010 at 12:20 AM, Darrin Chandler
dwchand...@stilyagin.comwrote:

 Hi,

 Trying to get up to speed in Haskell, I'm playing with doing some
 abstraction in data types. Specifically, I have this:

 type Cartesian_coord = Float

 type Latitude  = Float
 type Longitude = Float

 data Point  = Cartesian (Cartesian_coord, Cartesian_coord)
| Spherical (Latitude, Longitude)

 type Center = Point
 type Radius = Float

 data Shape  = Circle Center Radius
| Polygon [Point]

 This obviously stinks since a Polygon could contain mixed Cartesian and
 Spherical points. Polygon needs to be one or the other, but not mixed.

 I could define seperate types for Cartesian and Spherical and seperate
 CartesianPoly and SphericalPoly, but that doesn't seem very elegant and
 also increases as I add more coordinate systems and shapes. I read a
 little on GADTs, et al, but I'm not sure if that's what I want for this
 or not.

 Any help appreciated!

 --
 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsec monad transformer with IO?

2010-03-18 Thread Job Vranish
Hoogle is a great tool for finding haskell functions:

http://www.haskell.org/hoogle/

You can punch in the type of a function you want and it will give you a list
of functions that might do what you need.
Generalizing the types a bit usually helps. Searching for either  m a - n m
a   or   IO a - m a   would give you 'lift' and 'liftIO' as one of the top
results.

- Job

On Thu, Mar 18, 2010 at 1:58 PM, Stefan Klinger all-li...@stefan-klinger.de
 wrote:

 On 18 March 2010, Gregory Collins wrote with possible deletions:
  ParsecT has a MonadIO instance:
 
  class Monad m = MonadIO m where
  liftIO :: IO a - m a

 Thank you! I didn't see this. Great!

 Kind regards,
 Stefan


 --
 Stefan Klinger  o/klettern
/\/  bis zum
 send plaintext only - max size 32kB - no spam \   Abfallen
 http://stefan-klinger.de
 ___
 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] GPL answers from the SFLC (WAS: Re: ANN: hakyll-0.1)

2010-03-05 Thread Job Vranish
This seems really confusing.

It would imply that if I write a library that is designed to talk to some
part of the linux kernel API (which is GPL'd) then I'd have to release my
library under the GPL. And anything that used my libraries API would need to
be GPL'd too, etc...
Which would mean that everything run in linux would need to be GPL'd, which
is just silly.

- Job

On Fri, Mar 5, 2010 at 12:22 PM, Robert Greayer robgrea...@gmail.comwrote:

 Pending an explicit response from the SFLC, I decided to ask the FSF
 themselves what they thought of the Hackage/cabal situation.
 Specifically, I asked this:

  There is a website, 'Hackage' (http://hackage.haskell.org) that hosts
  source code packages for Haskell libraries and programs.  The site
  hosts *only* source code, along with (text) descriptions of the
  packages.  Each package hosted by the site is either source code for a
  library, for a program, or for both.

  In the package description, a package author specifies what license
  applies to the source code, the common choices being LGPL, GPL, or
  BSD3.  The package author also specifies what other packages in the
  repository the package may require to compile successfully.

  The controversy in the community of users who use Hackage is whether
  or not it is a violation of the GPL for a package to be uploaded to
  Hackage specifying (for example) a BSD3 license for the code in the
  package, but also specifying that another package is a requirement for
  compilation, where that other package has been uploaded specifying (a
  version of) the GPL as its license.

  The opinion of many in the community is that since Hackage hosts only
  source code, and does not in any way combine packages (any combination
  of packages is created when a user chooses to download and compile and
  link the individual packages) there is no problem: there are no
  'derived works' combining GPL and non-GPL being distributed on the
  site.

  Others believe that having a non-GPL package have as a dependency a
  GPL package is a problem for both the package author and for Hackage;
  that this in some way violates the GPL.

  I don't believe this sort of situation is clearly addressed in your
  FAQ (at least not to the satisfaction of the Hackage user community).
  There's a certain amount of fear, uncertainty and doubt being spread
  about usage of the GPL on Hackage, which it would be great to dispel
  (or, confirm, as necessary).


 Someone from the FSF responded as follows:

  A work which extends or requires a GPL work will generally also need to
  be released under the GPL, unless the GPL work provides a specific
  exception for that case. You are already familiar with the FAQ; however,
  please note http://www.fsf.org/licensing/licenses/gpl-faq.html#OOPLang
  and http://www.fsf.org/licensing/licenses/gpl-faq.html#MereAggregation .
  There is no magic to the act of linking, compiling, or a function
  invocation; these are not defining moments. It is the level of
  integration and dependency which will define whether one work is a
  derivative of another.

  Ultimately, the decision that one work is a derivative of another is a
  legal one which a court may have to decide for a particular case; a
  lawyer can give you a legal opinion. However, a good rule of thumb would
  be: if P is a GPL work, and Q is a work that would not function without
  P, then Q is probably a derivative of P and should only be conveyed to a
  third party or the public under a GPL license, in compliance with the
  license for P.

  I hope that helps.

  Thank you for your interest in free software!
  I am not a lawyer and the above is not legal advice.
  The opinions expressed above do not constitute an official position of
  the Free
  Software Foundation.

  Luigi Bai
  FSF Associate Member
  Volunteer, licens...@gnu.org

 Of course, given the disclaimer at the bottom, this opinion is officially
 no
 better than any of our opinions on the matter.  Nevertheless, I would at
 least believe based on the above that this is what the FSF *wants* the GPL
 to mean, and, by extension, would assume, barring other evidence that
 this is what someone who chooses the GPL *wants* it to mean, and in
 licensing any software that I write that depends on someone else's GPL'd
 software, I'd respect those desires (without at all suggesting that this
 has
 any bearing on how the GPL would actually be interpreted in court).

 There's still a lot of gray area here -- the mere existence of a dependency
 doesn't imply that a software package is useless without the dependency,
 so there are many situations in which P could depend on Q and not be
 a derivative of Q, because the dependency can be disabled in some way
 and the software would still function.  As an example -- pandoc can be
 built with or without highlighting-kate, and is useful either way.  They're
 both
 GPL and by the same author, so there's no issue, but were that not the
 case it would seem obvious 

Re: [Haskell-cafe] Haskell platform for GHC 6.12.1?

2010-03-04 Thread Job Vranish
I'm pretty sure you don't need mingw and all that. I've bootstrapped
cabal-install on windows a few times now without needing anything more than
ghc (though I haven't done 6.12 yet so I might be totally off base here...)

You can't use the nice bootstrap script, but you can download and build the
dependencies manually (and IIRC there are about 5 or so that don't come
included). Which is still a royal pain, but hopefully easier than all that
other messiness.

- Job

On Thu, Mar 4, 2010 at 4:38 AM, Peter Verswyvelen bugf...@gmail.com wrote:

 Using GHC 6.12.1 on Windows currently is hard, since one must compile
 the latest version of cabal-install, which is a nightmare to do for a
 typical windows user (install mingw, msys, utils like wget, download
 correct package from hackage, compile them in correct order, etc etc)

 What's the status of the Haskell platform for the latest and greatest
 Glasgow Haskell Compiler?
 ___
 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] ANNOUNCE: Parsec 3.1.0

2010-03-04 Thread Job Vranish
Sweet :)

I'm glad that notFollowedBy has been fixed. I've often had to redefine it
because the type was to restrictive.

- Job

On Wed, Mar 3, 2010 at 11:45 PM, Derek Elkins derek.a.elk...@gmail.comwrote:

 Parsec is a monadic combinator library that is well-documented, simple
 to use, and produces good error messages.   Parsec is not inherently
 lazy/incremental and is not well-suited to handling large quantities
 of simply formatted data.  Parsec 3 adds to Parsec the ability to use
 Parsec as a monad transformer and generalizes the input Parsec
 accepts.  Parsec 3 includes a compatibility layer for Parsec 2 and
 should be a drop-in replacement for code using Parsec 2.  Code using
 the features of Parsec 3 should use the modules in Text.Parsec.

 Due almost entirely to the work of Antoine Latter there is a new
 version of Parsec 3 available.  He documented some of his thoughts on
 this in this series of blog posts:
 http://panicsonic.blogspot.com/2009/12/adventures-in-parsec.html

 The main features of this release are:
- the performance should be much better and comparable to Parsec 2
- notFollowedBy's type and behavior have been generalized

 Changes:
- the changes to the core of Parsec lead to some changes to when
 things get executed when it is used as a monad transformer
In the new version bind, return and mplus no longer run in
 the inner monad, so if the inner monad was side-effecting for these
 actions the behavior of existing code will change.
- notFollowedBy p now behaves like notFollowedBy (try p) which
 changes the behavior slightly when p consumes input, though the
 behavior should be more natural now.
- the set of names exported from Text.Parsec.Prim has changed somewhat
 ___
 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] Real-time garbage collection for Haskell

2010-03-01 Thread Job Vranish
My current area of work is on realtime embedded software programming for
avionics systems. We do most of our coding in Ada but I've been dreaming of
using haskell instaed.

However, the garbage collector is actually one of the larger obsticles to
making this happen.

All of our avionics software needs to be certified by various regulatory
agencies, and there are varying levels of certification depending on
criticality. For the higher certification levels we would need to be able to
sure (or a least very very confidant) that the GC will collect everything
within a fixed amount of time, and that it won't take more than some fixed
amount of time per major from to do it.

A delay of a several milliseconds that could occur effectively at random is
completely unacceptable.

I would be very interested in alternative GC algorithms/approaches  that
would have a more deterministic/realtime behavior. I would be even be
willing to help out if there is other interest in this area :)


As a side note, I ran across an article on a way to use 100% reference
counting in a pure language by using weak references and being careful how
you preserve the weak/strong references during graph reduction:
http://comjnl.oxfordjournals.org/cgi/content/abstract/33/5/466
I don't want to pay $25 for the article though so I don't know how viable it
is. It would probably have lower performance than the current generational
GC but in this case I'd be willing to trade performance for determinism.
Has anyone heard of this algorithm before?

- Job


On Mon, Mar 1, 2010 at 9:53 AM, Thomas Schilling nomin...@googlemail.comwrote:

 On 28 February 2010 05:20, Luke Palmer lrpal...@gmail.com wrote:
  I have seen some proposals around here for SoC projects and other
  things to try to improve the latency of GHC's garbage collector.  I'm
  currently developing a game in Haskell, and even 100ms pauses are
  unacceptable for a real-time game.  I'm calling out to people who have
  seen or made such proposals, because I would be willing to contribute
  funding and/or mentor a project that would contribute to this goal.
  Also any ideas for reducing this latency in other ways would be very
  appreciated.

 There is a SoC project suggestion to implement Immix's ideas [1] in
 GHC's GC.  Both already use similar overall designs.  Both split the
 heap into regions which may employ different collection strategies.
 However, Immix does not address real-time issues.

 The main difficulty with real-time GC is that, while first-generation
 collection is usually very fast, eventually you just have to collect
 the old generation and you have to do it all at once.  Sun's new
 Garbage-First (G1) [2] collector therefore tracks pointers between
 regions, as opposed to just pointers from older two newer generations.
  This allows collecting regions independently (and in parallel).  G1
 is still stop-the-world, although marking phase is concurrent.
 Tracking pointers between all regions can result in quite substantial
 space overheads, however, so G1 uses some heuristics to discover
 popular objects and treats them specially.  In a personal
 conversation Simon Marlow expressed to me that he intends to go
 further into this direction, but I don't know how high-priority it is.
  In general I don't think true real-time is the goal in any case, but
 rather a general effort to keep GC-pauses short.

 Truly concurrent garbage collection is a whole different beast.
 Concurrent marking can be implemented efficiently with a write
 barrier.  I don't know of any fully concurrent GC scheme that gets by
 without a read barrier and significant space overhead, however.  There
 are certainly no plans from the GC HQ to implement a fully concurrent
 GC.

 [1]:
 http://www.cs.utexas.edu/users/speedway/DaCapo/papers/immix-pldi-2008.pdf
 [2]: http://research.sun.com/jtech/pubs/04-g1-paper-ismm.pdf

 --
 Push the envelope.  Watch it bend.
 ___
 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] Real-time garbage collection for Haskell

2010-03-01 Thread Job Vranish
On Mon, Mar 1, 2010 at 2:37 PM, Thomas Schilling nomin...@googlemail.comwrote:

 On 1 March 2010 16:27, Job Vranish job.vran...@gmail.com wrote:
  My current area of work is on realtime embedded software programming for
  avionics systems. We do most of our coding in Ada but I've been dreaming
 of
  using haskell instaed.

 A possible workaround would be to sprinkle lots of 'rnf's around your
 code to make sure you don't build up a thunk or two that will delay
 you later.  And if you do this, aren't you essentially programming in
 a strict functional language (like SML or O'Caml)?  By careful
 profiling you and auditing you can probably rule out most of the
 potential bad cases, so it can be acceptable for a soft real-time
 system (Galois did something like this, I believe).  But for avionics
 systems you probably want to more assurances than that, don't you?


Yes and no.
It's true that lazy evaluation makes reasoning about timings a bit more
difficult (and might not be usable in very time critical scenarios) but it
is still has well defined deterministic behavior.

It's the referential transparency that saves us here. If you run a lazy
function with the same objects (in the same evaluation state) it should
_theoretically_ take the same amount of time to run. All of our toplevel
inputs will be strict, and if we keep our frame-to-frame state strick, our
variances in runtimes, given the same inputs, should be quite low modulo the
GC.

Even our current code can take significantly different amounts of time to
compute things depending on what you're doing. Some waypoints take longer to
lookup from the database than others. Predicting the time to arrival can
take significantly longer/shorter depending on seemingly trivial parameters,
etc...

It matters less that code always takes the same amount of time to run
(though it needs to always be less than the frame time)  and more so that it
always takes the same amount of time to run given the same initial
conditions.

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


Re: [Haskell-cafe] save/restore of STRef state

2010-02-27 Thread Job Vranish
On Sat, Feb 27, 2010 at 11:53 AM, Andrew Coppin andrewcop...@btinternet.com
 wrote:


 If you use something like the State or Reader monad, it becomes trivial to
 temporarily modify the carried state. But maybe something like this is
 occasionally useful. (In particular, it seems to allow you to restore to a
 point not necessarily matching the most recent save.)


Yeah, in cases where you only need references to values of the same type,
then a Map in a state or Reader works really well.

But in my case I need to reference values of several different types, which
would make things messy in a state monad, and saving/restoring even messier.
I'm also using MonadFix quite a bit and a Map in a State monad was a lot
harder to make lazy (in my case, sometimes it's not to bad).


 Deriving the Eq instance for ContextRef means that it will compare the key
 *and* the IORef. Which gives the right answer, but seems rather redundant.
 Comparing the key alone should be sufficient.


Agree, will fix.

Why an IORef? Why not an STRef? Then you won't need unsafeIOToST. (And since
 the type system forces a ContextRef to exist in only one state thread,
 worrying about thread isolation with atomicModifyIORef seems unecessary.)


I use the IORefs because I wanted to use mkWeakIORef (maybe mkWeak would
work just as well?) and atomicModifyIORef. The thread isolation is needed
because of the the finalizers that clean out the map when the references get
GC'd.

Although, it _is_ kinda ugly. I'm thinking I might switch back STRefs and
just use unsafeCoerce *flinch* when I want to use atomicModifyIORef. (IORef
is just a newtype around STRef)


 Using a state monad with a mutable structure as the state looks highly
 dubious. (The whole point of a state monad is, after all, to avoid needing
 to mutate stuff.) I can see 2 calls to get, but none to put. I would
 suggest you either use a reader monad with mutable state, or a state monad
 with immutable state. One or the other. (Personally, I'd go for the latter.)


Yeah, I'll switch to Reader, but the state needs to be mutable so that the
finalizers can get to it.


 I'm also not 100% sure how the saving and restoring part works. Map Int (IO
 (IO ())) sounds fruity though.

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


Thanks for the feedback :)

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


[Haskell-cafe] haskell-src type inference algorithm?

2010-02-11 Thread Job Vranish
Anyone know of a type inference utility that can run right on haskell-src
types? or one that could be easily adapted?
I want to be able to pass in an HsExp and get back an HsQualType. It doesn't
have to be fancy, plain Haskell98 types would do.

It wouldn't be to hard to make one myself, but I figured there might be one
floating around already and it'd be a shame to write it twice :)

Thanks,

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


Re: [Haskell-cafe] matrix question

2010-02-02 Thread Job Vranish
I have a little haskell matrix library for fixed sized matricies on github:
http://github.com/jvranish/VectorMatix
which I've just realized is horribly out of date...I'll update it tonight
and probably push it to hackage too...

but if you're really want to stick with the [[Double]] type,
you can add a Foldable and Traversable instance to ZipLists and do this:

instance Foldable ZipList where
  foldMap f (ZipList x) = foldMap f x

instance Traversable ZipList where
  traverse f (ZipList x) = ZipList $ traverse f x

toZipList a = ZipList $ fmap ZipList a
fromZipList a = getZipList $ fmap getZipList a

multMM :: (Num a) = [[a]] - [[a]] - [[a]]
multMM a b = fromZipList $ multMMA (toZipList a) (toZipList b)

-- I about fell off my chair when I discovered you could do matrix
multiplication like this:
multMMA :: (Traversable f, Num a, Applicative f, Applicative row,
Applicative col, Traversable col) =
   row (f a) - f (col a) - row (col a)
multMMA a b = traverse (liftA2 dot a . pure) (sequenceA b)

dot :: (Foldable t, Num a, Applicative t) = t a - t a - a
dot a b = sum $ pure (*) * a * b


My matrix library uses a Gaussian elimination function (which operates on
lists) as well as det and inv functions which should be easily adaptable to
work on lists.

I'll make sure to push the updated code up tonight.

- Job





On Tue, Feb 2, 2010 at 7:15 AM, 조광래 kwangrae...@gmail.com wrote:

 define functions

 type Matrix=[[Double]]

 multMM :: Matrix - Matrix - Matrix --multiplies two matrices
 det :: Matrix - Double --computes the determinant of a matrix
 inv :: Matrix - Matrix --inverts a matrix

 i stuck on those problems

 can any one help me out?

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


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


Re: [Haskell-cafe] Re: OT: Literature on translation of lambda calculus to combinators

2010-01-29 Thread Job Vranish
Cool, Thanks :D

also quickcheck says the two algorithms are equivalent :)



On Fri, Jan 29, 2010 at 4:33 AM, Nick Smallbone nick.smallb...@gmail.comwrote:

 Job Vranish jvran...@gmail.com writes:

  Ideally we'd like the type of convert to be something like:
  convert :: LambdaExpr - SKIExpr
  but this breaks in several places, such as the nested converts in the RHS
 of the rule:
  convert (Lambda x (Lambda y e)) | occursFree x e = convert (Lambda x
 (convert (Lambda y e)))
 
  A while ago I tried modifying the algorithm to be pure top-down so that
 it wouldn't have this problem, but I
  didn't have much luck.
 
  Anybody know of a way to fix this?

 The way to do it is, when you see an expression Lambda x e, first
 convert e to a combinatory expression (which will have x as a free
 variable, and will obviously have no lambdas). Then you don't need
 nested converts at all.

 Not-really-tested code follows.

 Nick

 data Lambda = Var String
| Apply Lambda Lambda
| Lambda String Lambda deriving Show

 data Combinatory = VarC String
 | ApplyC Combinatory Combinatory
  | S
 | K
 | I deriving Show

 compile :: Lambda - Combinatory
 compile (Var x) = VarC x
 compile (Apply t u) = ApplyC (compile t) (compile u)
 compile (Lambda x t) = lambda x (compile t)

 lambda :: String - Combinatory - Combinatory
 lambda x t | x `notElem` vars t = ApplyC K t
 lambda x (VarC y) | x == y = I
 lambda x (ApplyC t u) = ApplyC (ApplyC S (lambda x t)) (lambda x u)

 vars :: Combinatory - [String]
 vars (VarC x) = [x]
 vars (ApplyC t u) = vars t ++ vars u
 vars _ = []

 ___
 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] OT: Literature on translation of lambda calculus to combinators

2010-01-28 Thread Job Vranish
There is a nice simple algorithm on wikipedia:
http://en.wikipedia.org/wiki/Combinatory_logic
(for both SKI and BCKW)

translated to haskell:

-- The anoying thing about the algorithm is that it is difficult to separate
the SKI and LC expression types
--  it's easiest to just combine them.
data Expr = Apply Expr Expr
  | Lambda String Expr
  | Id String
  | S
  | K
  | I
  deriving (Show)

convert (Apply a b) = Apply (convert a) (convert b)
convert (Lambda x e) | not $ occursFree x e = Apply K (convert e)
convert (Lambda x (Id s)) | x == s = I
convert (Lambda x (Lambda y e)) | occursFree x e = convert (Lambda x
(convert (Lambda y e)))
convert (Lambda x (Apply e1 e2)) = Apply (Apply S (convert $ Lambda x e1))
(convert $ Lambda x e2)
convert x = x

occursFree var (Apply a b) = (occursFree var a) || (occursFree var b)
occursFree var (Lambda a b) = if a == var then False else (occursFree var b)
occursFree var (Id a) = if a == var then True else False
occursFree var _ = False

testExpr = Lambda x $ Lambda y $ Apply (Id y) (Id x)

test = convert testExpr


Hope that helps,

- Job

2010/1/28 Dušan Kolář ko...@fit.vutbr.cz

 Dear cafe,

  Could anyone provide a link to some paper/book (electronic version of both
 preferred, even if not free) that describes an algorithm of translation of
 untyped lambda calculus expression to a set of combinators? Preferably SKI
 or BCKW. I'm either feeding google with wrong question or there is no link
 available now...

  Thanks,

Dušan

 ___
 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] OT: Literature on translation of lambda calculus to combinators

2010-01-28 Thread Job Vranish

 Why is it difficult?


Ideally we'd like the type of convert to be something like:
convert :: LambdaExpr - SKIExpr
but this breaks in several places, such as the nested converts in the RHS of
the rule:
convert (Lambda x (Lambda y e)) | occursFree x e = convert (Lambda x
(convert (Lambda y e)))

A while ago I tried modifying the algorithm to be pure top-down so that it
wouldn't have this problem, but I didn't have much luck.

Anybody know of a way to fix this?

- Job

On Thu, Jan 28, 2010 at 10:21 AM, Felipe Lessa felipe.le...@gmail.comwrote:

 On Thu, Jan 28, 2010 at 09:23:23AM -0500, Job Vranish wrote:
  -- The anoying thing about the algorithm is that it is difficult to
 separate
  the SKI and LC expression types
  --  it's easiest to just combine them.

 Why is it difficult?

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

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


Re: [Haskell-cafe] Re: Why?

2009-12-10 Thread Job Vranish

 I won't mention the name so as not to offend anyone.


Oh I'm sure we can handle it ;)
Though I'm curious as to how a language could be effect free in a practical
sense, but not a strict one? could you give an example?


To answer your original question, there are many benefits haskell gains from
being a pure language. (And by pure I mean that functions have no side
effects, they can only give data to their environment via their return
value). I think the my biggest reason (though there are probably others) is
as follows:

Pure code is easier to reason about than impure code:
  When I program for work (we use ada, ick) and I find that a function is
returning a bad result it is very difficult to figure out where the
malfunction is. Is the function itself the problem? incorrect parameters?
some global flags setup incorrectly? Did I need to call another  function to
setup state before I called this one? In a pure language I can just check
the function inputs. Are they good? if yes, then the problem is in the
function, if no, then follow the value up the chain, etc...
  A simpler case would be a single variable in a large function. Say I trace
a bug down to a bad value in a particular variable in a big function. I have
to look at every place that the variable is modified in the function as well
as any places where the variable is passed to other functions by reference
_as well as_ the control flow from those mutations to the usage of the
variable in question. In a pure language If a variable doesn't have the
correct value I check the definition (there can only be one)
Data flow in a pure language is so much easier to follow/understand and you
never have to worry about the order of execution (which is what makes it
easy to implement lazy evaluation).

I have literally debugged _hundreds_ of errors in our codebase at work that
would _not have even been possible_ in a pure language.

The downside to purity is that sometimes it's slower (though this is
becoming less and less of an issue, sometimes it's even faster) and
sometimes it's much easier to mutate some state than pass a value back up a
big chain. But overall I much prefer purity, it make my life so much easier.


- Job



On Thu, Dec 10, 2009 at 11:15 AM, John D. Earle johndea...@cox.net wrote:

  To elaborate there is another language that is also a functional
 language. I won't mention the name so as not to offend anyone. It too is
 effect free, that is what makes it functional and it is a functional
 language in the true sense of the term, but it is not effect free in the
 sense that Haskell is effect free. This other language is effect free in
 every practical sense whereas Haskell is effect free in a strict sense.

 ___
 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] IORefs and weak pointers

2009-11-04 Thread Job Vranish
Wow, this looks like a bug to me. If it's not a bug, then it's horribly
unintuitive.
I extended your example in an effort to figure out what was going on.
Apparently weak pointers loath live IORefs:

import Data.IORef
import Data.Maybe
import System.Mem
import System.Mem.Weak

import Control.Monad

data A = A String
data B = B String (IORef Int)
showA (A s) = s
showB (B s _) = s

main = do
 -- works as expected:
 ref - return $ A A
 ptr - mkWeak ref 21 Nothing
 performGC
 print . isNothing = deRefWeak ptr
 print (showA ref)

 -- why doesn't this work?
 ref - liftM (B B) $ newIORef 42
 ptr - mkWeak ref 21 Nothing
 performGC
 print . isNothing = deRefWeak ptr
 print (showB ref)

 -- this works, wtf???
 ref - liftM (B B) $ return undefined
 ptr - mkWeak ref 21 Nothing
 performGC
 print . isNothing = deRefWeak ptr
 print (showB ref)


I don't think this is the expected behavior. The docs on Weak pointers don't
mention anything like this. I suspect something in the GC is getting
confused by the IORef somehow.

- Job



2009/11/2 Patai Gergely patai_gerg...@fastmail.fm

  Could mkWeakPair do what you want?
 
 http://haskell.org/ghc/docs/latest/html/libraries/base/System-Mem-Weak.html#v:mkWeakPair
 No, it's just a convenience function that doesn't help much, because the
 value already refers to the IORef anyway.

 Here's a minimal example to illustrate the problem:

 import Data.IORef
 import Data.Maybe
 import System.Mem
 import System.Mem.Weak

 main = do
  ref - newIORef 42
  ptr - mkWeak ref 21 Nothing
  performGC
  print . isNothing = deRefWeak ptr
  print = readIORef ref

 Depending on whether you compile with optimisations, the weak reference
 might be reported dead, even though the IORef is alive and kicking.
 Switching to mkWeakPair (or just mentioning ref in the value somehow)
 doesn't affect that.

  Or are you trying to do something else?
 The goal is to create mutable objects whose update codes are tracked by
 the main program, but they can be thrown out when all the other
 references to the objects are lost. Creating weak pointers with MutVar#s
 seems to do the trick, but I'm not confident if it is a solution I can
 trust...

 Gergely

 --
 http://www.fastmail.fm - A fast, anti-spam email service.

 ___
 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] IORefs and weak pointers

2009-11-02 Thread Job Vranish
Could mkWeakPair do what you want?
http://haskell.org/ghc/docs/latest/html/libraries/base/System-Mem-Weak.html#v:mkWeakPair

Or are you trying to do something else?

- Job


2009/11/2 Patai Gergely patai_gerg...@fastmail.fm

 Hello all,

 I wanted to create a weak pointer with an IORef as the key and something
 else as the value, but I saw no way to do it through the API provided.
 After some experimentation I came up with the following abomination for
 a solution:

 myWeakRef (IORef (STRef r)) v f =
  IO $ \s - case mkWeak# r v f s of (# s', w #) - (# s', Weak w #)

 This works perfectly when the code is compiled both with and without
 optimisations, but ghci chokes on it with an internal error. So my
 question is if I can expect this to work at least this much in the long
 run, or is it a hopelessly fragile hack?

 Gergely

 --
 http://www.fastmail.fm - Same, same, but different...

 ___
 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] Applicative but not Monad

2009-10-30 Thread Job Vranish
If you use a monad instance for ZipLists as follows:

instance Monad ZipList where
  return x = ZipList $ repeat x
  ZipList [] = _ = ZipList []
  xs = f = diagonal $ fmap f xs

(where diagonal pulls out the diagonal elements of a ziplist of ziplists)

It will satisfy all the monad laws _except_ when the function f (in xs =
f) returns ziplists of different length depending on the value passed to it.
If f always returns lists of the same length, the monad laws should still
hold even if the lists are not infinite in length.


I have a fixed size list type (http://github.com/jvranish/FixedList) that
uses an instance like this and it always satisfies the monad laws since the
length of the list can be determined from the type so f is forced to always
return the same size of list.

I hope that helps things make sense :)

- Job



On Fri, Oct 30, 2009 at 1:33 PM, Yusaku Hashimoto nonow...@gmail.comwrote:

 Thanks for fast replies! Examples you gave explain why all
 Applicatives are not Monads to me.

 And I tried to rewrite Bob's Monad instance for ZipList with (=).

 import Control.Applicative

 instance Monad ZipList where
  return = ZipList . return
  (ZipList []) = _ = ZipList []
  (ZipList (a:as)) = f = zlHead (f a) `zlCons` (ZipList as = f)

 zlHead :: ZipList a - a
 zlHead (ZipList (a:_)) = a
 zlCons :: a - ZipList a - ZipList a
 zlCons a (ZipList as) = ZipList $ a:as
 zlTail :: ZipList a - ZipList a
 zlTail (ZipList (_:as)) = ZipList as

 I understand if this instance satisfies the laws, we can replace $
 with `liftM` and * and `ap`. And I found a counterexample (correct
 me if I'm wrong).

 *Main Control.Monad getZipList $ (*) $ ZipList [1,2] * ZipList [3,4,5]
 [3,8]
 *Main Control.Monad getZipList $ (*) `liftM` ZipList [1,2] `ap` ZipList
 [3,4,5]
 [3,6]

 Cheers,
 -~nwn

 On Sat, Oct 31, 2009 at 2:06 AM, Tom Davie tom.da...@gmail.com wrote:
  On Fri, Oct 30, 2009 at 5:59 PM, Luke Palmer lrpal...@gmail.com wrote:
 
  On Fri, Oct 30, 2009 at 10:39 AM, Tom Davie tom.da...@gmail.com
 wrote:
   Of note, there is a sensible monad instance for zip lists which I
   *think*
   agrees with the Applicative one, I don't know why they're not monads:
   instance Monad (ZipList a) where
 return = Ziplist . return
 join (ZipList []) = ZipList []
 join (ZipList (a:as)) = zlHead a `zlCons` join (map zlTail as)
 
  IIRC, that doesn't satisfy the associativity law, particularly when
  you are joining a list of lists of different lengths.  2 minutes of
  experimenting failed to find me the counterexample though.
 
  Cool, thanks Luke, that explains why this is available in Stream, but not
 in
  ZipList too.
  Bob
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Test cases for type inference

2009-10-21 Thread Job Vranish
I was recently working on an type inference algorithm and to test it I did
the following:
  Used the quickcheck Arbitrary typeclass to generate expressions
  Inferred types of the expressions using my algorithm,
  converted the expressions that passed inference to haskell and wrote them
to a file (without type signatures)
  converted and wrote the failed expression to a separate file
  compiled the passed file with -Wall, and extracted all the type
signatures that were spit out as warnings
  parsed the type signatures that -Wall spit out and compare with the
signatures generated by my algorithm.
  compiled the failed file and make sure I get type errors for all my
expressions

My algorithm also infers infinite types (which haskell does not) so I had to
test that functionality manually.

Overall it was kinda messy, but it worked ok.

I could possibly send you one of my lists. My test expressions are all very
simple, no type classes, only 2 types (function and number), and the only
expression components are let, lambda, apply, identifier, and number. If
something like that would work, let me know.

Hope that helps,

- Job


On Tue, Oct 20, 2009 at 10:07 AM, Peter Verswyvelen bugf...@gmail.comwrote:

 For learning, I would like to develop my own implementation of type
 inference, based on the paper Typing Haskell in Haskell.

 At first sight, the source code of THIH contains a small number of
 tests, but I was wandering if a large test set exist?

 Thanks,
 Peter
 ___
 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] Why there is not standard Monoid instance for ZipList a?

2009-10-16 Thread Job Vranish
Nope,
Other than possibly adding library clutter.

I have a package that provides many instances and common functions for
ZipLists. Eventually I might stick it on hackage, but currently it's here:
http://github.com/jvranish/ZipList

I really with there was a way to switch Applicative (or other) instances for
list (or other) types.
Then we wouldn't have this problem.

- Job


On Fri, Oct 16, 2009 at 5:52 AM, Vladimir Reshetnikov 
v.reshetni...@gmail.com wrote:

 I find the following instance very convenient:
 
 import Data.Monoid
 import Control.Applicative
 instance Monoid a = Monoid (ZipList a) where
   mempty = pure mempty
   mappend = liftA2 mappend
 

 Any reason why it is not in the standard library?

 Thanks,
 Vladimir

 ___
 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] Genuine Need For Persistent Global State?

2009-10-16 Thread Job Vranish
Stable pointers might do what you want:
http://haskell.org/ghc/docs/latest/html/libraries/base/Foreign-StablePtr.html

Though an IORef would probably work just as well, depending on how you
needed to use it..

- Job

On Fri, Oct 16, 2009 at 2:59 PM, Alan Carter alangcar...@gmail.com wrote:

 Hi,
 I've been looking at the patches given by Tom at Beware the Jabberwolk, for
 building Linux kernel modules in Haskell. Once I'd got Tom's stuff building,
 the next thing was to build a little driver which actually does something.
 Step by step I was making progress, and I've now got a little function which
 can see all the characters which are catted to the device file. That's when
 I got stuck.

 Trouble is, my function is (ultimately) being called from the C kernel
 stuff. It isn't on the bottom of a call graph coming from a Haskell main. A
 driver really needs to know where it's at. So I seem to need some kind of
 global, persistent state, and Control.Monad.State seems to be out because I
 can't pass a State around my call graph.

 I've thought about trying to create some State when I initialize, pass some
 kind of pointer back to the C shim which actually does the calling into
 Haskell, and then passing it back into Haskell on the writes and reads, but
 that seems dangerous because the Haskell garbage collector would
 (understandably) get the wrong idea and delete it. Also it's ugly - having
 to use C for something Haskell can't do.

 I've been looking at the Halfs Haskell file system, which surely must have
 solved its own version of this problem, but whatever it does in its FSState
 seems very complicated and is beyond my comprehension :-(

 So my questions are:

 1) Am I right in thinking that I have a genuine need for global, persistent
 state?
 2) Halfs works. Am I right in thinking it has (somehow) solved this
 problem?
 3) Is there a simple way to maintain global persistent state that I can
 stash between calls into a function, and access without needing to pass the
 state in? If so, is there an example anywhere?

 Thanks in advance,

 Alan

 --
 ... the PA system was moaning unctuously, like a lady hippopotamus reading
 A. E. Housman ...
  -- James Blish, They Shall Have Stars

 ___
 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] Num instances for 2-dimensional types

2009-10-05 Thread Job Vranish
You are in luck!

Such an instance is very simple with Applicative. If the type you want a Num
instance for is a member of the Applicative type class you can define it
like this:

instance (Num a) = Num (Vector2 a) where
  a + b = pure (+) * a * b
  a - b = pure (-) * a * b
  a * b = pure (*) * a * b
  negate a = pure negate * a
  abs a = pure abs * a
  signum = fmap signum
  fromInteger = pure . fromInteger

If you want to define a Num instance for _all_ applicatives, you can do this
(you'll need a couple extensions):

instance (Num a, Applicative f, Eq (f a), Show (f a)) = Num (f a) where
  a + b = pure (+) * a * b
  a - b = pure (-) * a * b
  a * b = pure (*) * a * b
  negate a = pure negate * a
  abs a = pure abs * a
  signum = fmap signum
  fromInteger = pure . fromInteger

I am currently working on a vector and matrix library for haskell that uses
instances of this form, which you can find here:
http://github.com/jvranish/VectorMatix.  The matrix half is very unfinished,
but the vector half is pretty much done.

Applicative is a pretty fantastic typeclass, it's definitly worth the time
to figure out how it works.

However, this technique won't work with tuples as they don't behave as
Functors in the way you would like. (too many type parameters, tuples don't
force all elements to be the same type so maps don't work, etc...)

Hope that helps :)

- Job



On Mon, Oct 5, 2009 at 8:40 AM, Sönke Hahn sh...@cs.tu-berlin.de wrote:

 Hi!

 I often stumble upon 2- (or 3-) dimensional numerical data types like

(Double, Double)

 or similar self defined ones. I like the idea of creating instances for Num
 for
 these types. The meaning of (+), (-) and negate is clear and very
 intuitive, i
 think. I don't feel sure about (*), abs, signum and fromInteger. I used to
 implement

fromInteger n = (r, r) where r = fromInteger n

 , but thinking about it,

fromInteger n = (fromInteger n, 0)

 seems very reasonable, too.

 Any thoughts on that? How would you do it?

 btw: These are two examples i looked at in hackage:
 Data.Complex.Complex (which is special, cause it is mathematically defined,
 what (*), abs, signum and fromInteger should do (i think))

 and

 Physics.Hipmunk.Common.Vector
 (
 http://hackage.haskell.org/packages/archive/Hipmunk/5.0.0/doc/html/Physics-
 Hipmunk-Common.html#9http://hackage.haskell.org/packages/archive/Hipmunk/5.0.0/doc/html/Physics-%0AHipmunk-Common.html#9
 )


 Sönke
 ___
 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] Num instances for 2-dimensional types

2009-10-05 Thread Job Vranish
In what way is it not a number?

data MyNumber a = MyNum a a
   deriving (Show, Eq)

instance Functor MyNum where
  fmap f (MyNum a b) = MyNum (f a) (f b)

instance Applicative MyNum where
  pure a = MyNum a a
  MyNum f g * MyNum a b = MyNum (f a) (g b)

instance (Num a) = Num (MyNum a) where
  a + b = pure (+) * a * b
  a - b = pure (-) * a * b
  a * b = pure (*) * a * b
  negate a = pure negate * a
  abs a = pure abs * a
  signum = fmap signum
  fromInteger = pure . fromInteger

This instance obeys the commutative, distributive, and associative laws,
and the multiplicative, and additive identities. (at least, if the numbers
it contains satisfy those laws)
How is MyNum not a number?


Sönke Hahn:
  btw, I forgot to mention in my first email, but
  fromInteger n = (r, r) where r = fromInteger n
  is better than:
  fromInteger n = (fromInteger n, 0)
 as you get a lot of corner cases otherwise.

 I use fromInteger = pure . fromInteger, which when combined with my
Applicative instance, is effectively the same as your:  fromInteger n = (r,
r) where r = fromInteger n


- Job

On Mon, Oct 5, 2009 at 9:12 AM, Miguel Mitrofanov miguelim...@yandex.ruwrote:



 Sönke Hahn wrote:

  I used to implement

fromInteger n = (r, r) where r = fromInteger n

 , but thinking about it,
fromInteger n = (fromInteger n, 0)

 seems very reasonable, too.


 Stop pretending something is a number when it's not.

 ___
 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] Splitting data and function declarations over multiple files

2009-10-01 Thread Job Vranish
Along the projection/co-algebra lines (I actually didn't know that's what
they were called until today :)  yay for learning new things!)

How about something like this:

-- Define prototypes for your class of actions here
data Actor = Actor {pos::Vector2 Float, move::Vector2 Float - Actor}

-- simple class that selects your actions based on type
class ActorClass a where
  mkActor :: a - Actor

-- object types
data Ball = Ball ...  -- stuff
data Paddle = Paddle ... -- stuff
data Wall = Wall ... -- suff

-- Functions for working with objects
getBallPosition (Ball ...) = ...
getPaddlePosition (Paddle ...) = ...

moveBall (Ball ...) = ...
movePaddle (Ball ...) = ...

-- selection actions for Ball
instance Actor Ball where
  mkActor this = let
pos' = getBallPosition this
move' v = moveBall this
in Actor pos' move'

-- selection actions for Paddle
instance Actor Paddle where
  mkActor this = let
pos' = getPaddlePosition this
move' v = movePaddle this
in Actor pos' move'


Base off a technique I ran across here:
http://www.mail-archive.com/hask...@haskell.org/msg04513.html

Also, a useful wikipage for doing OO things in haskell:
http://www.haskell.org/haskellwiki/OOP_vs_type_classes

- Job


On Thu, Oct 1, 2009 at 4:45 AM, Peter Verswyvelen bugf...@gmail.com wrote:

 I'm not sure if I understand what you mean with this co-algebraic approach,
 but I guess you mean that functions - like move - don't work directly on any
 datatype; you need to provide other functions that give access to the data.
 But that's basically what type classes do no? And that's also related to my
 earlier post of strong duck typing in Haskell.
 At least also in C#, that's the way I usually write code that works on any
 type, just make an interface or pass in a delegate.  I also know that my OO
 background keeps pushing me in the wrong direction when it comes to Haskell
 ;-)

 The collision handling approach is always interesting :)  In OO this is
 usually solved using multi-methods or visitors:
 http://en.wikipedia.org/wiki/Multiple_dispatch. What I usually did in old
 games of mine to handle collisions is not look at the type, but at the
 collision specific features of a type (which are again functions that
 extract information from the object), and that is most likely again the
 co-algebraic approach?

 On Wed, Sep 30, 2009 at 9:15 PM, Luke Palmer lrpal...@gmail.com wrote:

 On Wed, Sep 30, 2009 at 9:54 AM, Peter Verswyvelen bugf...@gmail.com
 wrote:
  I guess this is related to the expression problem.
  Suppose I have a datatype
  data Actor = Ball ... | Paddle ... | Wall ...
  and a function
  move (Ball ...) =
  move (Paddle ...) =
  move (Wall ...) =
  in Haskell one must put Actor and move into a single file.
  This is rather cumbersome if you work with multiple people or want to
 keep
  the files small and readable.
  Surely it is possible to use type classes, existentials, etc to split
 the
  data type into multiple ones, but that's already advanced stuff in a
 sense.

 You can do it without type classes and existentials.  The
 functionality you want is already supported by Haskell, you just have
 to let go of your syntactical expectations.  The trick is that you
 should rewrite your data type not as an algebra (a set of
 constructors), but as a coalgebra (a set of projections).

 Let's say your two open functions are:

 move :: Actor - Actor
 isAlive :: Actor - Bool

 This gives rise to the definition of an Actor type:

 data Actor = Actor { move :: Actor, isAlive :: Bool }

 And then the alternatives of your open data type are just values of type
 Actor:

 ball :: Vector - Vector - Actor
 ball pos vel = Actor {
move = ball (pos + vel) vel,
isAlive = True
  }

 etc.

 This trick works well until you get to the encoding of functions that
 pattern match on multiple Actors at the same time.  As far as I can
 tell, that cannot be encoded in this style in any reasonable way.
 Such functions must be rephrased in a coalgebraic style; i.e. instead
 of asking about constructors, using projection functions it knows are
 available.

 So for example instead of implementing collide by asking about
 pairs, add functions which report a shape function and a normal, or
 whatever your collide algorithm needs from shapes.

 You would probably end up having to do this anyway even with your
 proposed extension, because watch:

 partial data Actor = Ball ...

 collide (Ball ...) (Ball ...) = ...
 collide (Ball ...) x = ...

 We don't know about any other constructors, so the second line has to
 contain a pattern-free x.  So you would have to use projection
 functions to get any information about it, exactly as you would when
 you're writing in the coalgebraic style.

 So, Yes!  Haskell can do that!

 Luke



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


___

Re: [Haskell-cafe] Splitting data and function declarations over multiple files

2009-10-01 Thread Job Vranish
Opps, errors, it should be more like:

moveBall (Vector2 x y) (Ball ...) = ...
movePaddle (Vector2 x y) (Paddle ...) = ...

-- selection actions for Ball
instance Actor Ball where
  mkActor this = let
pos' = getBallPosition this
move' v = mkActor $ moveBall v this
in Actor pos' move'

-- selection actions for Paddle
instance Actor Paddle where
  mkActor this = let
pos' = getPaddlePosition this
move' v = mkActor $ movePaddle v this
in Actor pos' move'


Hmm, I bet some generics, or template haskell could clean up the extra
boilerplate associated with this technique.

- Job


On Thu, Oct 1, 2009 at 11:35 AM, Job Vranish jvran...@gmail.com wrote:

 Along the projection/co-algebra lines (I actually didn't know that's what
 they were called until today :)  yay for learning new things!)

 How about something like this:

 -- Define prototypes for your class of actions here
 data Actor = Actor {pos::Vector2 Float, move::Vector2 Float - Actor}

 -- simple class that selects your actions based on type
 class ActorClass a where
   mkActor :: a - Actor

 -- object types
 data Ball = Ball ...  -- stuff
 data Paddle = Paddle ... -- stuff
 data Wall = Wall ... -- suff

 -- Functions for working with objects
 getBallPosition (Ball ...) = ...
 getPaddlePosition (Paddle ...) = ...

 moveBall (Ball ...) = ...
 movePaddle (Ball ...) = ...

 -- selection actions for Ball
 instance Actor Ball where
   mkActor this = let
 pos' = getBallPosition this
 move' v = moveBall this
 in Actor pos' move'

 -- selection actions for Paddle
 instance Actor Paddle where
   mkActor this = let
 pos' = getPaddlePosition this
 move' v = movePaddle this
 in Actor pos' move'


 Base off a technique I ran across here:
 http://www.mail-archive.com/hask...@haskell.org/msg04513.html

 Also, a useful wikipage for doing OO things in haskell:
 http://www.haskell.org/haskellwiki/OOP_vs_type_classes

 - Job


 On Thu, Oct 1, 2009 at 4:45 AM, Peter Verswyvelen bugf...@gmail.comwrote:

 I'm not sure if I understand what you mean with this co-algebraic
 approach, but I guess you mean that functions - like move - don't work
 directly on any datatype; you need to provide other functions that give
 access to the data. But that's basically what type classes do no? And that's
 also related to my earlier post of strong duck typing in Haskell.
 At least also in C#, that's the way I usually write code that works on any
 type, just make an interface or pass in a delegate.  I also know that my OO
 background keeps pushing me in the wrong direction when it comes to Haskell
 ;-)

 The collision handling approach is always interesting :)  In OO this is
 usually solved using multi-methods or visitors:
 http://en.wikipedia.org/wiki/Multiple_dispatch. What I usually did in old
 games of mine to handle collisions is not look at the type, but at the
 collision specific features of a type (which are again functions that
 extract information from the object), and that is most likely again the
 co-algebraic approach?

 On Wed, Sep 30, 2009 at 9:15 PM, Luke Palmer lrpal...@gmail.com wrote:

 On Wed, Sep 30, 2009 at 9:54 AM, Peter Verswyvelen bugf...@gmail.com
 wrote:
  I guess this is related to the expression problem.
  Suppose I have a datatype
  data Actor = Ball ... | Paddle ... | Wall ...
  and a function
  move (Ball ...) =
  move (Paddle ...) =
  move (Wall ...) =
  in Haskell one must put Actor and move into a single file.
  This is rather cumbersome if you work with multiple people or want to
 keep
  the files small and readable.
  Surely it is possible to use type classes, existentials, etc to split
 the
  data type into multiple ones, but that's already advanced stuff in a
 sense.

 You can do it without type classes and existentials.  The
 functionality you want is already supported by Haskell, you just have
 to let go of your syntactical expectations.  The trick is that you
 should rewrite your data type not as an algebra (a set of
 constructors), but as a coalgebra (a set of projections).

 Let's say your two open functions are:

 move :: Actor - Actor
 isAlive :: Actor - Bool

 This gives rise to the definition of an Actor type:

 data Actor = Actor { move :: Actor, isAlive :: Bool }

 And then the alternatives of your open data type are just values of type
 Actor:

 ball :: Vector - Vector - Actor
 ball pos vel = Actor {
move = ball (pos + vel) vel,
isAlive = True
  }

 etc.

 This trick works well until you get to the encoding of functions that
 pattern match on multiple Actors at the same time.  As far as I can
 tell, that cannot be encoded in this style in any reasonable way.
 Such functions must be rephrased in a coalgebraic style; i.e. instead
 of asking about constructors, using projection functions it knows are
 available.

 So for example instead of implementing collide by asking about
 pairs, add functions which report a shape function and a normal, or
 whatever your collide algorithm needs from

Re: [Haskell-cafe] Market Place for Haskell development teams?

2009-09-29 Thread Job Vranish
 If there is demand for shops to work on smaller jobs in haskell then I
think a having a more specific marketplace/communication platform for
haskell work would be very helpful. If there is a perceived demand, supply
will soon follow.

- Job

On Tue, Sep 29, 2009 at 5:48 AM, Jörg Roman Rudnick 
joerg.rudn...@t-online.de wrote:

  These problems are critical -- but not hopeless, I think:

 (1) A simple technical matter, any average Haskell programmer (including
 myself...) can build a platform, e.g. in Happstack or the like, to clear
 this up (given you want to do this in Haskell ;-).

 (4) This is a special one, which I have pondered on some time ago. The
 customers' main concern seems to be will this company still support me in n
 years??
 o   if the project is interesting enough, I see hope there might be some
 academic unit willing to partake in this, as I have heard enough complaint
 of not having enough examples to demonstrate business relevance to students.
 Normally, the customer should have no problem in believing an academic unit
 and its interests to last some time.
 o   I would propose to pick up the insourcing concept -- as, what I can
 confirm by my own teaching experiences, it sometimes is easier to introduce
 Haskell to beginners (once the do have sufficient OS experience) then to
 people who already are adherents of some other language. Ok, we might need
 some more introductory literature etc.

 (3) Yes, there seem to be lots of people organized at a smaller level than
 what I described -- groups of one or very few members, working on a limited
 time range.

 Yesterday, I would have written there should be remarkable interest in
 greater projects, but, due to the poor resonance to my mail, I feel wary to
 do so now.

 (3)(2) Such a reserved reaction might indicate many Haskellers are not
 motivated by the money but by the fame, and -- as the lively succJava thread
 shows -- what could be greater fame (besides the evaluation of 42) than
 stealing the Java etc. community just another attractive project? ;-))

 Do I go wrong in saying there's a good deal of competitive spirit in the
 Haskell community interesting in taking claims away of other programming
 cultures which have grown saturated over the years? And, isn't the this
 *Haskeller bonus* indicating that doing the step to larger project should
 not be as hard as for others?

 A remaining issue might be a need for some facility to find cooperations
 and realize synergies -- see (1).

 Enough blah-blah. I got one email response (not posted to here) of a highly
 qualified Haskeller whom I could name two projects which might have
 interested him in his proximity, 80 miles and 75 miles away (and I do not
 have so many...). My learning is that a communication platform in this
 concern might be interesting to at least some of us. There are larger
 projects possible -- if we pick them up.


 All the best,

 Nick



 John A. De Goes wrote:


  It's very difficult to find information on:

  1. How many Haskell developers are out there;
 2. What a typical salary is for a Haskell developer;
 3. Whether or not the skills of a typical Haskell developer scale to large
 applications (most Haskell developers are hobby Haskellers and have only
 written tiny to small Haskell apps);
 4. How many shops are capable of handling Haskell development 
 maintenance.


  These are the kinds of information one needs to make an informed decision
 about whether to introduce Haskell into the workplace.

Regards,

  John A. De Goes
 N-Brain, Inc.
 The Evolution of Collaboration

  http://www.n-brain.net|877-376-2724 x 101

  On Sep 28, 2009, at 7:01 AM, Jörg Roman Rudnick wrote:

  In the last months, I made the experience it seems difficult to find
 commercial Haskell developer teams to take responsibility for projects in
 the range of $ 10.000 - 100.000. The Industrial Haskell Group does not seem
 to be the appropriate place for this, while harvesting Haskell team at
 general market places appears to be tedious.

 I would be very interested in others' experiences, and inhowfar my opinion
 is shared that there should be a demand for such a market place, for
 developer teams as well as those sympathizing with introducing Haskell
 somewhere.

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


 --

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



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


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


Re: [Haskell-cafe] Cal, Clojure, Groovy, Haskell, OCaml, etc.

2009-09-29 Thread Job Vranish
 Andrew Coppin andrewcop...@btinternet.com wrote:

 how do we fix all this?


I think the key here is to reduce the cost of contribution to a minimum.
Make it as easy as possible to contribute an example, or to fill in some
missing documentation (and to find it later).

Cabal and hackage have made it very easy to contribute and fetch packages
and I think this is the primary reason why there are so many hackage
packages. We need to make it even easier to contribute documentation.

I think having some haddock/wiki system that allowed user contributions
which could be displayed alongside the official package dos and an easy way
for package maintainers to incorporate the user supplied documentation into
the official package documentation would be very helpful.

To sum up:
1.  Make it stupidly easy to contribute documentation, notes, comments,
examples
2.  Make sure all of this good stuff can be easily accessed in one place.

- Job

On Tue, Sep 29, 2009 at 3:36 PM, Andrew Coppin
andrewcop...@btinternet.comwrote:

 Tom Tobin wrote:

 This.  As an experienced Pythonista but a beginning Haskeller, there
 is *no way* I would have been able to wrap my head around the basics
 of Haskell without the tutorage of Learn You A Haskell, Real World
 Haskell, and various smaller tutorials scattered around the Haskell
 wiki — but I still find the array of libraries confusing (just what
 comes with GHC — I'm not even talking about Hackage here), since the
 documentation seems to be quite terse compared to Python's docs.  I'm
 getting better at reading the code directly, but I'm often at a loss
 for what a particular library is good for in the first place.  The
 library documentation seems to assume a mathematical or (advanced)
 computer science background, and has no problem sending a reader off
 to see a journal paper for details — not exactly friendly to those who
 are trying their hardest to unlearn their imperative ways as it is.
 ;-


 While some of the stuff that comes with GHC is quite well documented,
 others are highly under-documented. (As an exercise, go count how many
 module descriptions say inspired by the paper by XXX at this URL...)

 Admittedly, the System.IO module probably isn't the place to explain what a
 monad is and write a full tutorial on using them. However, look at (say)
 Control.Concurrent.STM.TVar. In my copy (GHC 6.10.3) it lacks even type
 signatures, let alone actual descriptions. Similarly, Parsec has some lovely
 external documentation (unfortunately as a single giant HTML page), but the
 Haddock stuff is bare.

 Now, the operative question (and I'm sure we've debated this one before)
 is: how do we fix all this?


 ___
 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] Strong duck typing / structural subtyping / type class aliases / ??? in Haskell

2009-09-25 Thread Job Vranish
Short answer: There is no good way of doing what you want.
This is actually one of my biggest annoyances with haskell (right up there
with disallowing infinite types). They are many techniques that work better
or worse depending on the application, but non are very satisfactory IMO.
Your typeclass solution(or some variant of) is pretty much your best option.
If you're careful about how you define your datatype and classes you can
avoid the type families and such, but the whole point is to not have to be
careful.
If your types are fixed (which is usually true as long as you're not using
existentials) you might be able to get away with using
-XDisambiguateFieldRecords

If you want anything better you're probably going to have to use some form
of preprocessor (like OHaskell).


Supposedly OCaml has an OO feature that does this but I haven't tried it
out.

I would suspect that the reason why haskell doesn't provide duck typeing on
record fields is that analisys for optimizations is much more complicated
(as it currently stands, records are nothing but sugar on top of algeraic
datatypes).
You can end up with all sorts of weird things with duck typeing on record
fields, like unnamed datatypes. For example:

(using class constraint style to inidicate a record field restriction for
lack of a better syntax)
setPosition :: (position a) =Vector - a - a
setPosition v x = x { position = v }

translate :: (position a) =Vector - a - a
translate v x = x { position = v + (position x) }

getPosition :: (position a) = a - Vector
getPosition x = position x

result :: Vector
result = getPosition $ translate someVector $ setPosition someOtherVector

The type variable 'a' in these functions is never fixed to a specific type,
and it actually doesn't need to be. The compiler would just have to invent a
suitable one (a type with only the field 'position' of type Vector).

Maybe someday haskell will finially implement good, clean, duck typeable,
record functionality. I will be waiting...

- Job


On Fri, Sep 25, 2009 at 9:54 AM, Peter Verswyvelen bugf...@gmail.comwrote:

 Haskell's records are a bit annoying, and type-classes often group together
 too many methods, which means you make early decisions about future unknown
 requirements, and IMO you always get it wrong :-)
 After having read an email in the cafe about the Noop language  Self
 language, I realized that what I really would like to have is strong duck
 typing on records (or is it called structural subtyping? or
 prototype-based-objects? or something like that)
 For example (silly example full of inaccuracies, but you get the picture):

 class HasPosition a where
   position :: a - Point
   withPosition :: Point - a - a

 class HasVelocity a where
   velocity :: a - Vector
   withVelocity :: Vector - a - a

 which we really should write as

 field HasPosition :: Point
 field HasVelocity :: Vector

 And then

 record IsKinetic :: HasPosition HasVelocity

 suppose we write a function like

 kineticEulerStep dt k = withPosition (position k .+^ dt *^ velocity k) k

 kineticEulerStep will work on any type a that HasPosition and HasVelocity,
 and would get inferred signature

 kineticEulerStep :: IsKinetic a = Float - a - a

 which is identical to

 kineticEulerStep :: (HasPosition a, HasVelocity a) = Float - a - a

 So basically kineticEulerStep accepts anything that HasPosition and
 HasVelocity, whatever it is.

 So if it walks like a duck and ..., then it is a duck, but statically
 known...

 We could also do

 field HasForce :: Vector
 field HasMass :: Float

 record IsDynamic :: IsKinetic HasForce HasMass

 acceleration d = force d ^/ mass d
 withAcceleration a d = withForce (a ^* mass d) d

 dynamicEulerStep dt d = withVelocity (velocity d ^+^ dt *^ acceleration d)

 Of course you would also need type families to be really correct since
 Vector, Point, etc should also be parametrized.

 And really kineticEulerStep might also work on something that HasVelocity
 and HasAcceleration (since the code in dynamicEulerStep is almost the same
 as kineticEulerStep), so better abstraction might be needed.

 I'm not sure what kind of overhead a system like this would have in
 Haskell, since I suspect the many dictionaries are often not optimized away.

 I think for Haskell prime, something like this was 
 suggestedhttp://repetae.net/recent/out/classalias.html,
 but is was rejected?

 Languages like OCaml and haXe http://haxe.org/manual/2_types also
 provide a similar feature?

 I would like to collect ways of doing this in Haskell, without boilerplate,
 and preferably without runtime overhead.

 I remember reading OOHaskell a while time ago, and while I didn't
 understand a lot of it, I recall it also was doing a similar thing, but
 since the compiler lacks native support, the error messages you get most
 likely make it impossible to figure out what is going wrong. I think
 Grapefruit's Records, HList, Data.Accessor, etc.. might also work.

 Any guidelines and comments regarding 

Re: [Haskell-cafe] weak pointers and memoization (was Re: memoization)

2009-09-18 Thread Job Vranish
Yeah it seems like the general solution to the problem would be some sort of
map-like datastructure that you add items via a key/value pair, and if the
key gets GC'd, that entry gets removed from the structure.

I've been wanting something like this as well, but didn't know about weak
references so I didn't know if it was possible, but I think I could make
something like this now. I'll give it a shot and let you guys know how it
goes.

Rodney could you post your memo code that uses the weak references?

- Job

On Fri, Sep 18, 2009 at 7:56 AM, Peter Verswyvelen bugf...@gmail.comwrote:

 I would also like to see a solution for problems like these.

 Haskell provides a lot of nice memoizing / caching data structures -
 like a trie - but the ones I know indeed keep growing, so no garbage
 collection takes place?

 It would be nice to have a data structure that performs caching but
 does not grow unlimited.

 I had a similar problem with stable names; it is not possible to check
 if a stable name is still alive.

 On Fri, Sep 18, 2009 at 1:39 AM, Rodney Price rodpr...@raytheon.com
 wrote:
  In my case, the results of each computation are used to generate a node
  in a graph structure (dag).  The key, oddly, is a hash of a two-tuple
  that gets stored in the data structure after the computation of the
  node finishes.  If I don't memoize the function to build a node, the
  cost of generating the tree is exponential; if I do, it's somewhere
  between linear and quadratic.
 
  Another process prunes parts of this graph structure as time goes on.
  The entire data structure is intended to be persistent, lasting for
  days at a time in a server-like application.  If the parts pruned
  aren't garbage collected, the space leak will eventually be
  catastrophic.  Either the memo table or the graph structure itself will
  outgrow available memory.
 
  -Rod
 
 
  On Thu, 17 Sep 2009 13:32:13 -0400
  Job Vranish jvran...@gmail.com wrote:
 
  What are you trying to use this for? It seems to me that for memo
  tables you almost never have references to they keys outside the
  lookup table since the keys are usually computed right at the last
  minute, and then discarded (otherwise it might be easier to just
  cache stuff outside the function).
 
  For example with a naive fibs, the values you are passing in are
  computed, and probably don't exist before you do the recursive call,
  and then are discarded shortly afterward.
 
  It seems like putting a cap on the cache size, and then just
  overwriting old entries would be better.
  Am I missing something?
 
  - Job
 
 
 
  On Wed, Sep 16, 2009 at 4:48 PM, Rodney Price rodpr...@raytheon.com
  wrote:
 
   How does garbage collection work in an example like the one below?
   You memoize a function with some sort of lookup table, which stores
   function arguments as keys and function results as values.  As long
   as the function remains in scope, the keys in the lookup table
   remain in memory, which means that the keys themselves always
   remain reachable and they cannot be garbage collected.  Right?
  
   So what do you do in the case where you know that, after some
   period of time, some entries in the lookup table will never be
   accessed?  That is, there are no references to the keys for some
   entries remaining, except for the references in the lookup table
   itself.  You'd like to allow the memory occupied by the keys to be
   garbage collected.  Otherwise, if the function stays around for a
   long time, the size of the lookup table always grows.  How do you
   avoid the space leak?
  
   I notice that there is a function in Data.IORef,
  
   mkWeakIORef :: IORef a - IO () - IO (Weak (IORef a))
  
   which looks promising.  In the code below, however, there's only one
   IORef, so either the entire table gets garbage collected or none of
   it does.
  
   I've been reading the paper Stretching the storage manager: weak
   pointers and stable names in Haskell, which seems to answer my
   question.  When I attempt to run the memoization code in the paper
   on the simple fib example, I find that -- apparently due to lazy
   evaluation -- no new entries are entered into the lookup table, and
   therefore no lookups are ever successful!
  
   So apparently there is some interaction between lazy evaluation and
   garbage collection that I don't understand.  My head hurts.  Is it
   necessary to make the table lookup operation strict?  Or is it
   something entirely different that I am missing?
  
   -Rod
  
  
   On Thu, 10 Sep 2009 18:33:47 -0700
   Ryan Ingram ryani.s...@gmail.com wrote:
  
   
memoIO :: Ord a = (a - b) - IO (a - IO b)
memoIO f = do
   cache - newIORef M.empty
   return $ \x - do
   m - readIORef cache
   case M.lookup x m of
   Just y - return y
   Nothing - do let res = f x
 writeIORef cache $ M.insert x res m
 return res
   
memo

Re: [Haskell-cafe] weak pointers and memoization (was Re: memoization)

2009-09-18 Thread Job Vranish
Hey it works :D
Here is a proof of concept:
http://gist.github.com/189104

Maybe later today I'll try to make a version that can be safely used outside
IO.

- Job


On Fri, Sep 18, 2009 at 10:19 AM, Job Vranish jvran...@gmail.com wrote:

 Yeah it seems like the general solution to the problem would be some sort
 of map-like datastructure that you add items via a key/value pair, and if
 the key gets GC'd, that entry gets removed from the structure.

 I've been wanting something like this as well, but didn't know about weak
 references so I didn't know if it was possible, but I think I could make
 something like this now. I'll give it a shot and let you guys know how it
 goes.

 Rodney could you post your memo code that uses the weak references?

 - Job


 On Fri, Sep 18, 2009 at 7:56 AM, Peter Verswyvelen bugf...@gmail.comwrote:

 I would also like to see a solution for problems like these.

 Haskell provides a lot of nice memoizing / caching data structures -
 like a trie - but the ones I know indeed keep growing, so no garbage
 collection takes place?

 It would be nice to have a data structure that performs caching but
 does not grow unlimited.

 I had a similar problem with stable names; it is not possible to check
 if a stable name is still alive.

 On Fri, Sep 18, 2009 at 1:39 AM, Rodney Price rodpr...@raytheon.com
 wrote:
  In my case, the results of each computation are used to generate a node
  in a graph structure (dag).  The key, oddly, is a hash of a two-tuple
  that gets stored in the data structure after the computation of the
  node finishes.  If I don't memoize the function to build a node, the
  cost of generating the tree is exponential; if I do, it's somewhere
  between linear and quadratic.
 
  Another process prunes parts of this graph structure as time goes on.
  The entire data structure is intended to be persistent, lasting for
  days at a time in a server-like application.  If the parts pruned
  aren't garbage collected, the space leak will eventually be
  catastrophic.  Either the memo table or the graph structure itself will
  outgrow available memory.
 
  -Rod
 
 
  On Thu, 17 Sep 2009 13:32:13 -0400
  Job Vranish jvran...@gmail.com wrote:
 
  What are you trying to use this for? It seems to me that for memo
  tables you almost never have references to they keys outside the
  lookup table since the keys are usually computed right at the last
  minute, and then discarded (otherwise it might be easier to just
  cache stuff outside the function).
 
  For example with a naive fibs, the values you are passing in are
  computed, and probably don't exist before you do the recursive call,
  and then are discarded shortly afterward.
 
  It seems like putting a cap on the cache size, and then just
  overwriting old entries would be better.
  Am I missing something?
 
  - Job
 
 
 
  On Wed, Sep 16, 2009 at 4:48 PM, Rodney Price rodpr...@raytheon.com
  wrote:
 
   How does garbage collection work in an example like the one below?
   You memoize a function with some sort of lookup table, which stores
   function arguments as keys and function results as values.  As long
   as the function remains in scope, the keys in the lookup table
   remain in memory, which means that the keys themselves always
   remain reachable and they cannot be garbage collected.  Right?
  
   So what do you do in the case where you know that, after some
   period of time, some entries in the lookup table will never be
   accessed?  That is, there are no references to the keys for some
   entries remaining, except for the references in the lookup table
   itself.  You'd like to allow the memory occupied by the keys to be
   garbage collected.  Otherwise, if the function stays around for a
   long time, the size of the lookup table always grows.  How do you
   avoid the space leak?
  
   I notice that there is a function in Data.IORef,
  
   mkWeakIORef :: IORef a - IO () - IO (Weak (IORef a))
  
   which looks promising.  In the code below, however, there's only one
   IORef, so either the entire table gets garbage collected or none of
   it does.
  
   I've been reading the paper Stretching the storage manager: weak
   pointers and stable names in Haskell, which seems to answer my
   question.  When I attempt to run the memoization code in the paper
   on the simple fib example, I find that -- apparently due to lazy
   evaluation -- no new entries are entered into the lookup table, and
   therefore no lookups are ever successful!
  
   So apparently there is some interaction between lazy evaluation and
   garbage collection that I don't understand.  My head hurts.  Is it
   necessary to make the table lookup operation strict?  Or is it
   something entirely different that I am missing?
  
   -Rod
  
  
   On Thu, 10 Sep 2009 18:33:47 -0700
   Ryan Ingram ryani.s...@gmail.com wrote:
  
   
memoIO :: Ord a = (a - b) - IO (a - IO b)
memoIO f = do
   cache - newIORef M.empty
   return $ \x - do

Re: [Haskell-cafe] code-build-test cycle

2009-09-18 Thread Job Vranish
Yeah linking in windows is _very_ slow. Supposedly this is because the
linker forks a lot of processes. In linux this is fine as forking is dirt
cheap, but in windows (at least older versions, not completely sure about
vista or 7) forking is expensive.

Building a Qt app on my EEE in linux only takes a couple seconds. Building
in windows on my dual core 3.2Ghz machine takes 15-30 seconds.  It's pretty
sad.

I second Bulat's suggestion. If you can compile everything and just use ghci
to avoid the link you should be able to get the best of both works.

- Job


On Fri, Sep 18, 2009 at 12:34 AM, Bulat Ziganshin bulat.zigans...@gmail.com
 wrote:

 Hello Michael,

 Friday, September 18, 2009, 6:42:32 AM, you wrote:

  Now I'm wondering if Hugs is a faster interpreter.

 2x slower, and incompatib;e with qtHaskell

  meaningful way without compilation. Any advice welcome. Maybe there is a
  way to speed up the interpretation.

 if compilation is fast and only linking is slow, you may recompile
 haskell modules every time but use ghci to omit linking. just execute ghc
 compilation command inside ghci before running your app


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

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

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


Re: [Haskell-cafe] Re: [Haskell-beginners] map question

2009-09-17 Thread Job Vranish
(-) happens to be the only prefix operator in haskell, it also an infix
operator.
so:
 4 - 2
2
 -3
-3

 ((-) 5) 3  -- note that in this case (-) is treated like any regular
function so 5 is the first parameter
2
 (5 - ) 3
2
 (-5 )
-5
 (flip (-) 5) 3
-2


It's a little wart brought about by the ambiguity in common mathematical
syntax.
If you play around in ghci you should get the hang of it pretty quick.

- Job



On Thu, Sep 17, 2009 at 11:08 AM, Gregory Propf gregorypr...@yahoo.comwrote:

 Remember that there is asymmetry between (+) and (-).  The former has the
 commutative property and the latter does not so:

 (+) 3 4 = 7

 and

 (+) 4 3 = 7

 but

 (-) 3 4 = -1

 and

 (-) 4 3 = 1

 --- On *Thu, 9/17/09, Tom Doris tomdo...@gmail.com* wrote:


 From: Tom Doris tomdo...@gmail.com
 Subject: Re: [Haskell-beginners] map question
 To: Joost Kremers joostkrem...@fastmail.fm
 Cc: beginn...@haskell.org
 Date: Thursday, September 17, 2009, 6:06 AM

 This works:

 map (+ (-1)) [1,2,3,4]


 2009/9/17 Joost Kremers 
 joostkrem...@fastmail.fmhttp://mc/compose?to=joostkrem...@fastmail.fm
 

 Hi all,

 I've just started learning Haskell and while experimenting with map a bit,
 I ran
 into something I don't understand. The following commands do what I'd
 expect:

 Prelude map (+ 1) [1,2,3,4]
 [2,3,4,5]
 Prelude map (* 2) [1,2,3,4]
 [2,4,6,8]
 Prelude map (/ 2) [1,2,3,4]
 [0.5,1.0,1.5,2.0]
 Prelude map (2 /) [1,2,3,4]
 [2.0,1.0,0.,0.5]

 But I can't seem to find a way to get map to substract 1 from all members
 of the
 list. The following form is the only one that works, but it doesn't give
 the
 result I'd expect:

 Prelude map ((-) 1) [1,2,3,4]
 [0,-1,-2,-3]

 I know I can use an anonymous function, but I'm just trying to understand
 the
 result here... I'd appreciate any hints to help me graps this.

 TIA

 Joost


 --
 Joost Kremers, PhD
 University of Frankfurt
 Institute for Cognitive Linguistics
 Grüneburgplatz 1
 60629 Frankfurt am Main, Germany
 ___
 Beginners mailing list
 beginn...@haskell.org http://mc/compose?to=beginn...@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners



 -Inline Attachment Follows-

 ___
 Beginners mailing list
 beginn...@haskell.org http://mc/compose?to=beginn...@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners



 ___
 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] weak pointers and memoization (was Re: memoization)

2009-09-17 Thread Job Vranish
What are you trying to use this for? It seems to me that for memo tables you
almost never have references to they keys outside the lookup table since the
keys are usually computed right at the last minute, and then discarded
(otherwise it might be easier to just cache stuff outside the function).

For example with a naive fibs, the values you are passing in are computed,
and probably don't exist before you do the recursive call, and then are
discarded shortly afterward.

It seems like putting a cap on the cache size, and then just overwriting old
entries would be better.
Am I missing something?

- Job



On Wed, Sep 16, 2009 at 4:48 PM, Rodney Price rodpr...@raytheon.com wrote:

 How does garbage collection work in an example like the one below?  You
 memoize a function with some sort of lookup table, which stores function
 arguments as keys and function results as values.  As long as the
 function remains in scope, the keys in the lookup table remain in
 memory, which means that the keys themselves always remain reachable
 and they cannot be garbage collected.  Right?

 So what do you do in the case where you know that, after some period of
 time, some entries in the lookup table will never be accessed?  That is,
 there are no references to the keys for some entries remaining, except
 for the references in the lookup table itself.  You'd like to allow the
 memory occupied by the keys to be garbage collected.  Otherwise, if the
 function stays around for a long time, the size of the lookup table
 always grows.  How do you avoid the space leak?

 I notice that there is a function in Data.IORef,

 mkWeakIORef :: IORef a - IO () - IO (Weak (IORef a))

 which looks promising.  In the code below, however, there's only one
 IORef, so either the entire table gets garbage collected or none of it
 does.

 I've been reading the paper Stretching the storage manager: weak
 pointers and stable names in Haskell, which seems to answer my
 question.  When I attempt to run the memoization code in the paper on
 the simple fib example, I find that -- apparently due to lazy
 evaluation -- no new entries are entered into the lookup table, and
 therefore no lookups are ever successful!

 So apparently there is some interaction between lazy evaluation and
 garbage collection that I don't understand.  My head hurts.  Is it
 necessary to make the table lookup operation strict?  Or is it
 something entirely different that I am missing?

 -Rod


 On Thu, 10 Sep 2009 18:33:47 -0700
 Ryan Ingram ryani.s...@gmail.com wrote:

 
  memoIO :: Ord a = (a - b) - IO (a - IO b)
  memoIO f = do
 cache - newIORef M.empty
 return $ \x - do
 m - readIORef cache
 case M.lookup x m of
 Just y - return y
 Nothing - do let res = f x
   writeIORef cache $ M.insert x res m
   return res
 
  memo :: Ord a = (a - b) - (a - b)
  memo f = unsafePerformIO $ do
  fmemo - memoIO f
  return (unsafePerformIO . fmemo)
 
  I don't think there is any valid transformation that breaks this,
  since the compiler can't lift anything through unsafePerformIO.  Am I
  mistaken?
 
-- ryan

 ___
 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] Peano axioms

2009-09-17 Thread Job Vranish
The problem is that you are using 'suc' as if it is a constructor: ((suc m)
`eq` (suc n) =  m `eq` n)
You'll have to change it to something else, and it will probably require
adding an unpacking function to your class and it will probably be messy.
I'd suggest you make use of the Eq typeclass and defined the Eq instances
separately:

class (Eq n) = Peano2 n where
 one :: n
 plus :: n - n - n
 suc :: n - n
 suc a = a `plus` one

- Job

On Thu, Sep 17, 2009 at 2:36 PM, pat browne patrick.bro...@comp.dit.iewrote:

 Hi,
 Below are two attempts to define Peano arithmetic in Haskell.
 The first attempt, Peano1, consists of just a signature in the class
 with the axioms in the instance. In the second attempt, Peano2, I am
 trying to move the axioms into the class. The reason is, I want to put
 as much specification as possible into the class. Then I would like to
 include properties in the class such as commutativity something like:
 infixl 5 `com`
 com :: Int - Int - Int
 x `com` y  = (x + y)
 commutative com a b = (a `com` b) == (b `com` a)

 I seem to be able to include just one default equation the Peano2 attempt.
 Any ideas?
 I have looked at
 http://www.haskell.org/haskellwiki/Peano_numbers

 Regards,
 Pat

 -- Attempt 1
 -- In this attempt the axioms are in the instance and things seem OK
 module Peano1 where
 infixl 6 `eq`
 infixl 5 `plus`

 class Peano1 n where
  suc :: n - n
  eq :: n - n - Bool
  plus :: n - n - n

 data Nat = One | Suc Nat deriving Show


 instance  Peano1 Nat where
  suc = Suc
  One `eq` One = True
  (Suc m) `eq` (Suc n) =  m `eq` n
  _`eq`_  = False
  m `plus` One = Suc m
  m `plus` (Suc n) = Suc (m `plus` n)
 -- Evaluation *Peano1 Suc(One) `plus` ( Suc (One))





 -- Attempt 2
 -- In this attempt the axioms are in the class and things are not OK.
 module Peano2 where
 infixl 6 `eq`
 infixl 5 `plus`

 class Peano2 n where
  one :: n
  eq :: n - n - Bool
  plus :: n - n - n
  suc :: n - n
  suc a = a `plus` one

 {-
  I cannot add the remaining default axioms
  one `eq` one = True
  (suc m) `eq` (suc n) =  m `eq` n
  (suc a) `eq` (suc b) =  a `eq` b
  _`eq`_  = False
 -}

 ___
 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] Fixed length list type?

2009-09-09 Thread Job Vranish
Does anyone know of a hackage package that has fixed length list type that
is an instance of Applicative, Foldable and Traversable?
(a list type that somehow encodes its length in the type)

I've found lots of fixed length list types, but non that are members of the
common typeclasses.
I've implement one here:
http://github.com/jvranish/FixedList/blob/6c861a12ba5d17481fd22cdb1f90404abff7c0bc/src/Data/FixedList.hs

But am I just duplicating work that is already out there?

Thanks,

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


Re: [Haskell-cafe] ANNOUNCE: lenses -- Simple Functional Lenses

2009-09-03 Thread Job Vranish
Actually they are _not_ limited to only the state monad, they just work
naturally there. There are a few functions that allow you to easily use them
outside a state monad (fetch, update, alter).

It looks like the haddock documentation is generated now. There are a couple
simple examples for accessing nested state in the tutorial in the module
documentation here:
http://hackage.haskell.org/packages/archive/lenses/0.1.2/doc/html/Data-Lenses.html

Would a more complex example be helpful? I don't have time to post one now,
but perhaps in an hour or two.

Yeah, I decided to go with the state monad over making my own mathematically
beautiful datatype.  The state monad worked just too well all by itself. It
also has the advantage of not really needed any helper functions (other than
fromGetSet). All the important ones are already exist.

- Job


On Thu, Sep 3, 2009 at 5:50 AM, Martijn van Steenbergen 
mart...@van.steenbergen.nl wrote:

 Job Vranish wrote:

 A simple but powerful implementation of function lenses (aka functional
 references, accessors, etc..).


 Nice! I will definitely give it a whirl when I pick up my MUD again. I'm
 currently using accessors there. I see your functions are limited to use in
 the state monad--you're right, I've never used accessors outside of a state
 monad yet.

 I'm somewhat sad that you didn't capture lenses in a datatype, because it
 is such a nice example of a Category instance. I would like to see how to
 compose lenses to access deeper fields--I use nested data structures and
 would like to modify fields that are hidden deeper in the state. Can you
 perhaps add an example to show that?

 Thanks!

 Martijn.


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


Re: [Haskell-cafe] Re: cabal: : openFile: does not exist (No such file or directory)

2009-09-02 Thread Job Vranish
Did you by chance use the prebuilt ghc binaries? or build ghc manually?

- Job

On Mon, Aug 31, 2009 at 5:23 PM, Paulo Tanimoto tanim...@arizona.eduwrote:

 Hello,

 On Mon, Aug 31, 2009 at 3:29 PM, Job Vranishjvran...@gmail.com wrote:
  I got around this problem by downgrading to 6.10.3 (I think I rebuilt
 cabal
  as well)
 
  I'm not sure if the problem is with cabal, GHC, or some 64bit ubuntu
  library. (probably a combination of ghc+64bit ubuntu)
 
  Does anybody have ghc 6.10.4 working on 64bit Ubuntu?
 
  - Job
 

 I'm using GHC 6.10.4 from HQ + Platform on Ubuntu Jaunty 64bit and
 don't have this problem.  Let me know if you want to compare settings.

 Paulo

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


Re: [Haskell-cafe] Cabal install specific version of a package

2009-09-02 Thread Job Vranish
cabal install derive-0.1.4

On Wed, Sep 2, 2009 at 1:12 PM, Grigory Sarnitskiy sargrig...@ya.ru wrote:

 How to install specific version of a package (derive 0.1.4)?
 ___
 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] ANNOUNCE: lenses -- Simple Functional Lenses

2009-09-02 Thread Job Vranish
A simple but powerful implementation of function lenses (aka functional
references, accessors, etc..).

This library provides a convenient way to access and update the elements of
a structure. It is very similar to Data.Accessors, but simpler, a bit more
generic and has fewer dependencies. I particularly like how cleanly it
handles nested structures in state monads. It also contains a couple simple
functions that can be used to easily convert a function that fetches data
from a structure to a function that modifies data in the structure.

Hackage hasn't generated the haddock documentation yet, but there is a
mini-tutorial in Data.Lenses that explains it's use.
Also for those that are interested it's also hosted on github here:
http://github.com/jvranish/Lenses/tree/master

Let me know what you think,
Criticism is welcome,

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


Re: Re[2]: [Haskell-cafe] GUI library

2009-09-01 Thread Job Vranish
Deallocation is automatic (just like C++ Qt)

C++ Qt has excellent unicode support. I haven't explicit tried it in
qtHaskell, but as far as I know it should work just fine.

Unfortunatly it does not currently build just with cabal, however the build
scripts are very clean (no configure) and the haskell half is cabalized.
 To build on windows you only need the haskell platform and the Qt SDK
(and then you either have to put the ghc path into Qts qtEnv.bat (what I
did), or you have to put the Qt paths into the system path) and then you run
the qtHaskells build.bat and you're done.
 To build on linux you need the haskell platform and Qt4 dev libraries
(they are probably in your distros package manager) and then you run the
qtHaskells build script, and your done. Umm, with one gotcha, on my system I
had to replace two instances of 'gmake' in the build script with 'make'. You
might not have to do that on your system.

Qt uses the native APIs to draw controls, so your apps look appropriate on
different platforms.

- Job

On Tue, Sep 1, 2009 at 12:43 AM, Bulat Ziganshin
bulat.zigans...@gmail.comwrote:

 Hello Job,

 Tuesday, September 1, 2009, 1:16:38 AM, you wrote:

  I recommend qtHaskell.

 how it's in areas of
 - memory deallocation when it's no more need - is it automatic or
 manual?
 - unicode support
 - compatibiliy with latest ghc versions - does it build by Cabal or we
 need to wait while gurus release installers for Windows?
 - does it use native GUI controls on Windows or draws them itself?

 i'm asking because those questions arise when using other libs


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


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


Re: [Haskell-cafe] GUI library

2009-09-01 Thread Job Vranish
If you're already used to C++ Qt and PyQt, qtHaskell should be relatively
straightforward (though probably with a few gotchas).
You could download qtHaskell and look at the examples to get an idea for the
feel of it. If you're already used to Qt they should look familiar.

Subclassing _is_ done a little weird:

First you declare a dummy datatype:

data MyQPushButton = MyQPushButton

And then you use the qSubClass function:

myQPushButton :: String - IO (QPushButton MyQPushButton)
myQPushButton s = qSubClass $ qPushButton1 s

The type signature here is necessary. It's the only thing that forces the
new (QPushButton a) to be a QPushButton MyQPushButton.

Then you can use your subclassed buttons like so:

main :: IO ()
main = do
app - qApplication
dialog - qDialog
button1 - myQPushButton Click for Stuff
qObject_connectSlot1 button1 clicked() button1 click() $
on_pbutton_clicked dialog
mainLayout - qVBoxLayout
qLayout_addWidget mainLayout button1
qWidget_setLayout dialog mainLayout
qWidget_setWindowTitle dialog Stuff Test
ok - qDialog_exec dialog
return()

on_pbutton_clicked :: QDialog () - QPushButton MyQPushButton - IO ()
on_pbutton_clicked _dlg _this  = do
mb - qMessageBox1 _dlg
qMessageBox_setText mb $ Stuff
qWidget_show mb
return ()

Hmmm, though it doesn't look like you can currently overload methods of your
parent class, usually you don't need too though as you can just tie into a
signal (so you still can do things like paint). Though I'm kinda suprised I
didn't notice this before, I'll have to email the guy and see if this is
actually an issue.

Also, qtHaskell doesn't fully support all the Qt widgets (though it covers
most of them) but there is a new version coming out soon that should be more
complete.

Overall qtHaskell has served my perposes well.

There is also a good listing of GUI toolkits for Haskell at
http://www.haskell.org/haskellwiki/Applications_and_libraries/GUI_libraries

- Job

On Tue, Sep 1, 2009 at 1:49 AM, Michael Mossey m...@alumni.caltech.eduwrote:

 Thanks for the info. Interesting. I'm already familiar with C++ Qt and also
 PyQt. I am also a fan of Qt.

 However, as a beginner to Haskell, I want to be sure I don't get myself
 into trouble. I hope that qtHaskell is straightforward.

 Qt depends on deriving user classes. How is this handled in qtHaskell?

 Thanks,

 -Mike


 Job Vranish wrote:

 I recommend qtHaskell.
 I am a big fan of Qt in general. It has good documentation and extensive
 examples, is very well designed, and has a good license. I'd even say the
 C++ version is good choice for beginners (certainly easier to understand/use
 than say GTK).
 The qtHaskell bindings are also pretty good. The documentation and
 examples are not as extensive, but you can usually use the C++ documentation
 to fill in the gaps.
 Being already familiar with C++ Qt, using qtHaskell was a snap. However,
 if you're unfamiliar with both Qt and Haskell it will probably be confusing
 at first. Though I'd bet money the GTK bindings aren't any better in that
 regard.
 I'd still say you'd be more productive with qtHaskell in the long run.

 - Job


 On Sat, Aug 29, 2009 at 11:03 AM, Michael Mossey 
 m...@alumni.caltech.edumailto:
 m...@alumni.caltech.edu wrote:

I want to choose a GUI library for my project. Some background: I'm
a beginner to functional programming and have been working through
Haskell books for a few months now. I'm not just learning Haskell
for s**ts and giggles; my purpose is to write
music-composition-related code; in particular, I want to write a
graphical musical score editor. (Why write my own editor, you may
ask? Because I want to fully integrate it with
computer-assisted-composition algorithms that I plan to write, also
in Haskell.) I decided to use Haskell for its great features as a
functional programming language.

Regarding a choice of GUI library, I want these factors:

- it needs to provide at a minimum a drawing surface, a place I can
draw lines and insert characters, in addition to all the standard
widgets and layout capabilities we have to come to expect from a GUI
library.

- This is a Windows application.

- it needs to be non-confusing for an intermediate-beginner
Haskeller. Hopefully good documentation and examples will exist on
the web.

- It might be nice to have advanced graphics capability such as Qt
provides, things like antialiasied shapes, and a canvas with
efficient refresh (refereshes only the area that was exposed, and if
your canvas items are only primitives, it can do refreshes from
within C++ (no need to touch your Haskell code at all). However I'm
wondering if qtHaskell fits my criteria well-documented and lots
of examples aimed at beginners.

Thanks,
Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org mailto:Haskell

Re: [Haskell-cafe] Cleaning up stable names?

2009-09-01 Thread Job Vranish
Well usually, when I've used stable names, I've just used them to check if
things are the same, and then thrown them away. So no chance for a space
leak. It's usually unsafe to keep stable names around for very long as they
can lose their ability to tell if two things are the same (if this surprises
you, you should carefully reread
http://haskell.org/ghc/docs/latest/html/libraries/base/System-Mem-StableName.html#v%3AmakeStableName).

Out of curiosity, how are you planning on using them?

- Job

On Tue, Sep 1, 2009 at 3:40 AM, Peter Verswyvelen bugf...@gmail.com wrote:

 but without that function, stable names are not that useful I guess? they
 would cause a space leak?

 On Mon, Aug 31, 2009 at 10:59 PM, Job Vranish jvran...@gmail.com wrote:

 I also would like a isStableNameTargetAlive function.
 Though if you had such a function then you probably _could_ make a
 deRefStableName function, which, since there isn't one, probably means
 that such a function would be hard to make.

 - Job

 On Sun, Aug 30, 2009 at 4:54 PM, Peter Verswyvelen bugf...@gmail.comwrote:

 From the documentation, I don't think I grasp how stable names work.
 From the docs:
 There is no deRefStableName operation. You can't get back from a stable
 name to the original Haskell object. The reason for this is that the
 existence of a stable name for an object does not guarantee the existence of
 the object itself; it can still be garbage collected.

 From this I can conclude that stable names behave a bit like weak
 pointers.

 However, suppose I have a hash table of these stable names. How can I
 remove the redundant stable names from the table? I mean removing stable
 names that refer to an object that is garbage collected? I don't see any
 function for checking that (e.g. isStableNameTargetAlive or something)

 Thanks,
 Peter





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




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


Re: [Haskell-cafe] Re: cabal: : openFile: does not exist (No such file or directory)

2009-08-31 Thread Job Vranish
I got around this problem by downgrading to 6.10.3 (I think I rebuilt cabal
as well)

I'm not sure if the problem is with cabal, GHC, or some 64bit ubuntu
library. (probably a combination of ghc+64bit ubuntu)

Does anybody have ghc 6.10.4 working on 64bit Ubuntu?

- Job

On Mon, Aug 31, 2009 at 2:43 PM, Fernando Henrique Sanches 
fernandohsanc...@gmail.com wrote:

 Sorry for ressurecting the thread, my I'm having the same problem here.

 Deleting the .cabal/config file shows only temporary results, and -v3 isn't
 helping:

 ~/sources/haskell-platform-2009.2.0.2 % cabal update
 Config file /home/fernando/.cabal/config not found.
 Writing default configuration to /home/fernando/.cabal/config
 Downloading the latest package list from hackage.haskell.org
 ~/sources/haskell-platform-2009.2.0.2 % cabal update
 cabal: :: openFile: does not exist (No such file or directory)
 ~/sources/haskell-platform-2009.2.0.2 % cabal update -v3
 cabal: ?: openFile: does not exist (No such file or directory)

 I'm on Ubuntu 9.04 x64. ghc 6.10.4

 This is the output of the mentioned describe-parsec command, but I don't
 know what to do with it:

 ~/sources/haskell-platform-2009.2.0.2 % ghc-pkg describe parsec-2.1.0.1
 name: parsec
 version: 2.1.0.1
 license: BSD3
 copyright:
 maintainer: Daan Leijen d...@cs.uu.nl
 stability:
 homepage: 
 http://www.cs.uu.nl/~daan/parsec.htmlhttp://www.cs.uu.nl/%7Edaan/parsec.html
 package-url:
 description: Parsec is designed from scratch as an industrial-strength
 parser
  library.  It is simple, safe, well documented (on the package
  homepage), has extensive libraries and good error messages,
  and is also fast.
 category: Parsing
 author: Daan Leijen d...@cs.uu.nl
 exposed: True
 exposed-modules: Text.ParserCombinators.Parsec.Language
  Text.ParserCombinators.Parsec.Token
  Text.ParserCombinators.Parsec.Error
  Text.ParserCombinators.Parsec.Char
  Text.ParserCombinators.Parsec.Combinator
  Text.ParserCombinators.Parsec.Expr
  Text.ParserCombinators.Parsec.Perm
  Text.ParserCombinators.Parsec.Pos
  Text.ParserCombinators.Parsec.Prim
 Text.ParserCombinators.Parsec
 hidden-modules:
 import-dirs: /usr/local/lib/parsec-2.1.0.1/ghc-6.10.4
 library-dirs: /usr/local/lib/parsec-2.1.0.1/ghc-6.10.4
 hs-libraries: HSparsec-2.1.0.1
 extra-libraries:
 extra-ghci-libraries:
 include-dirs:
 includes:
 depends: base-4.1.0.0
 hugs-options:
 cc-options:
 ld-options:
 framework-dirs:
 frameworks:
 haddock-interfaces: /usr/local/share/doc/parsec-2.1.0.1/html/parsec.haddock
 haddock-html: /usr/local/share/doc/parsec-2.1.0.1/html


 Fernando Henrique Sanches



 On Thu, Jul 30, 2009 at 7:52 AM, Mike Pentney mike.pent...@physics.orgwrote:

 I had a similar problem (on Ubuntu Incontinent Ibex). I'd previously
 installed ghc 6.8.x, and (among other things) cabal. When I decided to
 upgrade to the Haskell platform, I deleted ghc but not my original cabal
 installation.

 When I got the error, I deleted my (old) copy of

 ~/.cabal/config

 and it seemed to fix the problem. I'd assumed something in the config file
 was pointing to a file or directory that had been removed when I uninstalled
 ghc 6.8.x...

 HTH

 Mike.


 Job Vranish wrote:

 lol, yep you're right. I'd assumed the haskell platform shipped with the
 latest parsec, when in fact it does not :) my bad...

 However, I fixed the cabal issue by installing ghc 6.10.3 and rebuilding
 the haskell platform. Apparently there is either a compiler issue or
 incompatibility with 6.10.4 that causes the cabal: : openFile: does not
 exist (No such file or directory) error.

 - Job

 On Tue, Jul 28, 2009 at 10:44 AM, Thomas Hartman tphya...@gmail.commailto:
 tphya...@gmail.com wrote:

did you verify parsec-2.1.0.1 exports

Text.Parsec.Language

?

This might be a parsec 2 versus parsec 3 issue

ghc-pkg describe parsec-2.1.0.1

should tell you the answer to that.



2009/7/27 Job Vranish jvran...@gmail.com mailto:jvran...@gmail.com
 :

  I tried updating to ghc-6.10.4 and have exactly the same error.
  Also ghc doesn't seem to be able to find any of the haskell
 platform
  packages, even though it ghc-pkg finds them just fine.
 
  For example (trimmed for brevity):
 
  ghc-pkg list
  /usr/local/lib/ghc-6.10.4/./package.conf:
  Cabal-1.6.0.3,
  ...
  parsec-2.1.0.1, pretty-1.0.1.0, process-1.0.1.1,
 random-1.0.0.1,
  ...
 
  ghci -v readModel.hs
  GHCi, version 6.10.4: http://www.haskell.org/ghc/  :? for help
  Glasgow Haskell Compiler, Version 6.10.4, for Haskell 98, stage 2
booted by
  GHC version 6.8.2
  Using package config file: /usr/local/lib/ghc-6.10.4/./package.conf
  ...
 
  readModel.hs:9:7:
  Could not find module `Text.Parsec.Language':
locations searched

Re: [Haskell-cafe] Cleaning up stable names?

2009-08-31 Thread Job Vranish
I also would like a isStableNameTargetAlive function.
Though if you had such a function then you probably _could_ make a
deRefStableName function, which, since there isn't one, probably means that
such a function would be hard to make.

- Job

On Sun, Aug 30, 2009 at 4:54 PM, Peter Verswyvelen bugf...@gmail.comwrote:

 From the documentation, I don't think I grasp how stable names work.
 From the docs:
 There is no deRefStableName operation. You can't get back from a stable
 name to the original Haskell object. The reason for this is that the
 existence of a stable name for an object does not guarantee the existence of
 the object itself; it can still be garbage collected.

 From this I can conclude that stable names behave a bit like weak pointers.

 However, suppose I have a hash table of these stable names. How can I
 remove the redundant stable names from the table? I mean removing stable
 names that refer to an object that is garbage collected? I don't see any
 function for checking that (e.g. isStableNameTargetAlive or something)

 Thanks,
 Peter





 ___
 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] GUI library

2009-08-31 Thread Job Vranish
I recommend qtHaskell.
I am a big fan of Qt in general. It has good documentation and extensive
examples, is very well designed, and has a good license. I'd even say the
C++ version is good choice for beginners (certainly easier to understand/use
than say GTK).
The qtHaskell bindings are also pretty good. The documentation and examples
are not as extensive, but you can usually use the C++ documentation to fill
in the gaps.
Being already familiar with C++ Qt, using qtHaskell was a snap. However, if
you're unfamiliar with both Qt and Haskell it will probably be confusing at
first. Though I'd bet money the GTK bindings aren't any better in that
regard.
I'd still say you'd be more productive with qtHaskell in the long run.

- Job


On Sat, Aug 29, 2009 at 11:03 AM, Michael Mossey m...@alumni.caltech.eduwrote:

 I want to choose a GUI library for my project. Some background: I'm a
 beginner to functional programming and have been working through Haskell
 books for a few months now. I'm not just learning Haskell for s**ts and
 giggles; my purpose is to write music-composition-related code; in
 particular, I want to write a graphical musical score editor. (Why write my
 own editor, you may ask? Because I want to fully integrate it with
 computer-assisted-composition algorithms that I plan to write, also in
 Haskell.) I decided to use Haskell for its great features as a functional
 programming language.

 Regarding a choice of GUI library, I want these factors:

 - it needs to provide at a minimum a drawing surface, a place I can draw
 lines and insert characters, in addition to all the standard widgets and
 layout capabilities we have to come to expect from a GUI library.

 - This is a Windows application.

 - it needs to be non-confusing for an intermediate-beginner Haskeller.
 Hopefully good documentation and examples will exist on the web.

 - It might be nice to have advanced graphics capability such as Qt
 provides, things like antialiasied shapes, and a canvas with efficient
 refresh (refereshes only the area that was exposed, and if your canvas items
 are only primitives, it can do refreshes from within C++ (no need to touch
 your Haskell code at all). However I'm wondering if qtHaskell fits my
 criteria well-documented and lots of examples aimed at beginners.

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

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


Re: [Haskell-cafe] Re: Time constrained computation

2009-08-28 Thread Job Vranish
I tried this using timeout, but was never able to get it to work. The
timeout doesn't behave like I expect. I can take several seconds for it to
timeout, even with very low timeouts.

Any ideas?

- Job

module Main where

import Data.IORef
import System.Timeout
import System.IO.Unsafe

tailScan f (x:xs) = resultList
  where
resultList = x : zipWith f resultList xs

facts = 1 : tailScan (*) [1..]
fac n = facts !! n


eterm x n = x^n / (fac n)
eseries x = fmap (eterm x) [0..]
ePrecisionList x = tailScan (+) $ eseries x

computeUntil t xs = do
a - newIORef undefined
timeout t $ sequence $ fmap (writeIORef a) xs
readIORef a

-- compute e for only 10 microseconds
e x = computeUntil 10 (ePrecisionList x)

main = do
  -- compute e
  print = e 1



On Fri, Aug 28, 2009 at 9:01 AM, Mitar mmi...@gmail.com wrote:

 Hi!

 Ups, missed save button and pressed send. ;-)

 So I am not really sure if this is correct term for it but I am open
 to better (search) terms.

 I am wondering if it is possible to make a time constrained
 computation. For example if I have a computation of an approximation
 of a value which can take more or less time (and you get more or less
 precise value) or if I have an algorithm which is searching some
 search-space it can find better or worse solution depending how much
 time you allow. So I would like to say to Haskell to (lazily, if it
 really needs it) get me some value but not to spend more than so much
 time calculating it.

 One abstraction of this would be to have an infinity list of values
 and I would like to get the last element I can get in t milliseconds
 of computational time.

 One step further would be to be able to stop computation not at
 predefined time but with some other part of the program deciding it is
 enough. So I would have a system which would monitor computation and a
 pure computation I would be able to stop. Is this possible? Is it
 possible to have a pure computation interrupted and get whatever it
 has computed until then?

 How could I make this? Is there anything already done for it? Some
 library I have not found?

 Of course all this should be as performance wise as it is possible.

 So the best interface for me would be to be able to start a pure
 computation and put an upper bound on computation time but also be
 able to stop it before that upper bound. And all this should be as
 abstracted as it is possible.


 Mitar
 ___
 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] Applicative and Monad transformers

2009-08-27 Thread Job Vranish
You could test your instance using the checkers package on hackage (has
quickcheck properties for common typeclasses) to see if it fulfills the
applicative laws.

But I'm not sure if it is acceptable to define applicative instances that
don't match the monad instance.
Does anyone know of libraries that depend on applicative instances matching
their corresponding monad instance?

I've  often wanted an applicative instance for a datatype that didn't match
the monad instance.
For example, I find the zipping applicative list instance more useful than
the current choice applicative list instance
instance Applicative [] where
  pure x = repeat x
  fs * xs = zipWith ($) fs xs

This actually also has a corresponding Monad instance (with a couple
restrictions). It would be nice if there was a way to hide instances so that
they could be redefined.

- Job



On Wed, Aug 26, 2009 at 12:04 PM, Martijn van Steenbergen 
mart...@van.steenbergen.nl wrote:

 Jeremy Shaw wrote:

 What I would prefer is:

 instance (Monad f, Applicative f) = Applicative (ReaderT r f) where
pure a = ReaderT $ const (pure a)
f * a = ReaderT $ \r -  ((runReaderT f r) *
 (runReaderT a r))


 Right. This doesn't only go for ReaderT, it already goes for Either, too:
 you don't want the 'ap' implementation for * there either.

 These are beautiful examples of how applicative style gives the caller less
 power, but the callee more information, allowing more information to be
 retained. In this case it allows you to concatenate errors using mappend.

 Another example is parsing: I believe Doaitse's parsers allow more
 optimization if they are only used in applicative style (but I'm not sure of
 this).

 This shows there can be several sensible implementations of a type class.
 You ask which instance is right--that depends entirely on what you want it
 to do! Setting (*) = ap is just one of them, one you happen to get for
 free if your functor is already a monad.

 Hope this helps,

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

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


Re: [Haskell-cafe] Re: Keeping an indexed collection of values?

2009-08-21 Thread Job Vranish
Thanks for all the input! :)

My current code (unfinished) is here:
http://github.com/jvranish/IndexedCollection/tree/master
but I think I'll shorten the names as you suggest. (and add some strictness
to availableKeys)

I also added an extra phantom type parameter to the collection (and key) so
that I can prevent keys from being used on different collections even if
they hold elements of the same type.

There is still problem that trying to use a deleted key might return a bad
result rather than an error.
I'm not sure how to fix that one. I could keep another buffer, perhaps of
the last 100 or so deleted keys, so that a key doesn't get recycled until
100 other keys have been freed. This would increase the chances of detecting
this type of error.
I could also possibly integrate it with Bernie's suggestion, which would
probably significantly improve performance in my case. But the added
complexity might not be worth it.

Hmm although... I could potentially do something evil and detect the use of
a deleted key via stableNames. I'd rewrap my keys on recycle so that there
stablenames change.  Then I can check on lookup if the key used has the same
stableName as the key in the collection, if they don't match either raise an
error or return Nothing.
Not sure if I feel that evil though :D

Thanks again for the input :)

- Job


On Fri, Aug 21, 2009 at 7:26 AM, Heinrich Apfelmus 
apfel...@quantentunnel.de wrote:

 Heinrich Apfelmus wrote:
  Job Vranish wrote:
  I've been in a situation a lot lately where I need to keep a collection
 of
  values, and keep track of them by a persistent index.
 
 
 module Store (Key, Store, empty, add, delete, lookup) where
 
 newtype Key = Key { int :: Int }
 
 empty  :: Store a
 add:: a - Store a - (Key, Store a)
 delete :: Key - Store a - Store a
 lookup :: Key - Store a - Maybe a
 
  This way, the user doesn't know and care how  Key  is implemented.
 
  Last but not least, there is the issue that trying to use an already
  deleted key might yield a wrong result instead of an error. That
  shouldn't happen if used correctly, but might give a headache when
  debugging.

 There is even a very simple way to prevent at least some cases of
 misuse, when one key is accidentally used on stores of different type. A
 phantom parameter will do the trick:

newtype Key a = Key { int :: Int }

add:: a - Store a - (Key a , Store a)
delete :: Key a - Store a - Store a
lookup :: Key a - Store a - Maybe a



 Regards,
 apfelmus

 --
 http://apfelmus.nfshost.com

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

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


Re: [Haskell-cafe] Re: Keeping an indexed collection of values?

2009-08-21 Thread Job Vranish
It only requires type annotations on your uses of empty (as that is the only
way to construct a collection). The phantom type sticks to everything after
that.
If you don't care to add a signature then things still work just fine, you
just won't be prevented from using indexes from the wrong collection if the
the collection type is the same. I think this is nice, because if you are
working with just one collection, or collections of only different types you
probably don't want to care about the phantom type.
But if you do care, it adds extra protection.

For example:

data P1
data P2

to = runState
inCol = evalState

a = empty :: IndexedCollection Int P1
b = empty :: IndexedCollection Int P2

(i1, a') = add 5 `to` a
(i2, b') = add 16 `to` b

test = lookup i2 `inCol` a' -- type error, but type checks if no signatures
on a or b

- Job

On Fri, Aug 21, 2009 at 12:24 PM, Sebastian Fischer 
s...@informatik.uni-kiel.de wrote:


 On Aug 21, 2009, at 5:11 PM, Job Vranish wrote:

  I also added an extra phantom type parameter to the collection (and key)
 so that I can prevent keys from being used on different collections even if
 they hold elements of the same type.



 I have the impression that this requires explicit type annotations with
 your current solution which seems a bit tiresome. If not instantiated to
 specific different types, the additional phantom types of different
 collections can just be unified which does not lead to a type error.

 As you seem to implement a monadic interface, you might be able to steal
 the idea of using higher-rank polymorphism (that is used in the ST monad
 implementation) to ensure that the phantom types of different collections
 cannot be unified. But that would probably mean to implement your own monad
 that carries this phantom type too..

 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] Parsec lookahead and |

2009-08-20 Thread Job Vranish
Yeah, that's weird.  I played around with la and it seems to only cause
problems when the parser passed into lookAhead succeeds, which seem to go
directly against it's stated purpose.

lookAhead isn't  consuming, (hence the unexpected b) but still prevents
| from doing it's thing.

Seems like a bug to me...

My off the hip fix is a modified form of the ugly try:

lookAhead (ParsecT p)
= ParsecT $ \s@(State _ pos _) - do
res - p s
case res of
  Consumed rep - do r - rep
 case r of
   Error err - return $ Empty $ return $ Error
(setErrorPos pos err)
   Ok a state err - return $ Empty $ return $
Ok a s err
  empty- return $ empty


The only potential annoyance with this fix that I can see, is that the error
messages can be confusing if you are doing dumb things with your lookAhead
parsers. For example:

la :: Parsec String () (Char)
la = lookAhead' (char 'r')

*Main parseTest ((la  char 'a') | char 'b') a
parse error at (line 1, column 1):
unexpected a
expecting r or b
*Main parseTest ((la  char 'a') | char 'b') r
parse error at (line 1, column 2):
unexpected r
expecting a or b

But for the most part it behaves as expected.

- Job

(sorry for the double post Martijn, forgot to reply to all)

On Thu, Aug 20, 2009 at 7:44 AM, Martijn van Steenbergen 
mart...@van.steenbergen.nl wrote:

 Goedemiddag café,

 Consider the following function, using parsec-3.0.0:

  la :: Parsec String () (Maybe Char)
 la = lookAhead (optionMaybe anyChar)


 *Lookahead parseTest (char 'a' | char 'b') a
 'a'
 *Lookahead parseTest (char 'a' | char 'b') b
 'b'
 *Lookahead parseTest (la * char 'a' | char 'b') a
 'a'
 *Lookahead parseTest (la * char 'a' | char 'b') b
 parse error at (line 1, column 2):
 unexpected b
 expecting a

 The first three work fine and as expected, but the fourth example fails
 where I would expect success. I know | won't try the rhs if the lhs
 consumed input, but lookAhead's documentation promises not to consume any
 input. Is this a bug in Parsec or am I missing something?

 Thanks,

 Martijn.
 ___
 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] Right way to implement setPixel function

2009-08-20 Thread Job Vranish
Your setPixel function is almost ready to work in a State monad
If you modify your setPixel function slightly like so:

setPixel' :: Int - Int - Color - B.ByteString - ((), B.ByteString)
setPixel'  x y (r,g,b) image = ((), B.concat [beforePixel, pixel,
afterPixel])

and then wrap it in the State monad constructor:

setPixel = State setPixel'

then you can do

drawPixels = do
  setPixel 5 10 (200, 0, 0)
  setPixel 20 1 (0, 200, 0)
  setPixel 90 2 (0, 0, 200)

modifiedImage = execState drawPixels originalImage

See! you were already using a monad and didn't even know it! :D

Performance wise,  B.concat is O(n), which is very not good for your
purpose. It copies the whole string and the optimizer won't be able to
magically make it go away. For something that works in O(1), you will have
to use something like STArrays instead of bytestrings.

- Job



On Thu, Aug 20, 2009 at 2:32 AM, CK Kashyap ck_kash...@yahoo.com wrote:

 Hi,
 I had posted a note on line drawing algo with Haskell some time back. Now,
 I am trying to write a PNM image.

 import qualified Data.ByteString as B

 width = 256
 height = 256
 bytesInImage = width * height * 3
 blankImage =  B.pack $ take bytesInImage (repeat 0)

 type Color = (Int,Int,Int)
 setPixel :: B.ByteString - Int - Int - Color - B.ByteString
 setPixel image x y (r,g,b) = B.concat [beforePixel, pixel, afterPixel]
 where
 beforePixel = B.take before image
 afterPixel = B.drop (before+3) image
 pixel=B.pack [(fromIntegral r),(fromIntegral
 g),(fromIntegral b)]
 -- number of bytes before the 3 bytes of
 -- the pixel at x y
 before = (y * width * 3) + (x * 3) - 3

 main = do
 putStrLn P6
 putStrLn ( (show width) ++   ++ (show height) )
 putStrLn 255
 -- Set a red pixel at 100 100
 B.putStr (setPixel blankImage 100 100 (255,0,0))


 Can I please have some review comments on the code above? Would recreating
 the entire ByteString for each setPixel be an overhead?
 Also, I am barely beginning to grasp the Monad conceptI was wondering
 if there could be a monadic style of implementation of this - that could
 potentially have a series of setPixels inside a do block?

 Regards,
 Kashyap


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


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


Re: [Haskell-cafe] Right way to implement setPixel function

2009-08-20 Thread Job Vranish
Opps:
setPixel = State setPixel'

should be:
setPixel x y rgb = State $ setPixel' x y rgb

- Job

On Thu, Aug 20, 2009 at 1:05 PM, Job Vranish jvran...@gmail.com wrote:

 Your setPixel function is almost ready to work in a State monad
 If you modify your setPixel function slightly like so:

 setPixel' :: Int - Int - Color - B.ByteString - ((), B.ByteString)
 setPixel'  x y (r,g,b) image = ((), B.concat [beforePixel, pixel,
 afterPixel])

 and then wrap it in the State monad constructor:

 setPixel = State setPixel'

 then you can do

 drawPixels = do
   setPixel 5 10 (200, 0, 0)
   setPixel 20 1 (0, 200, 0)
   setPixel 90 2 (0, 0, 200)

 modifiedImage = execState drawPixels originalImage

 See! you were already using a monad and didn't even know it! :D

 Performance wise,  B.concat is O(n), which is very not good for your
 purpose. It copies the whole string and the optimizer won't be able to
 magically make it go away. For something that works in O(1), you will have
 to use something like STArrays instead of bytestrings.

 - Job



 On Thu, Aug 20, 2009 at 2:32 AM, CK Kashyap ck_kash...@yahoo.com wrote:

 Hi,
 I had posted a note on line drawing algo with Haskell some time back. Now,
 I am trying to write a PNM image.

 import qualified Data.ByteString as B

 width = 256
 height = 256
 bytesInImage = width * height * 3
 blankImage =  B.pack $ take bytesInImage (repeat 0)

 type Color = (Int,Int,Int)
 setPixel :: B.ByteString - Int - Int - Color - B.ByteString
 setPixel image x y (r,g,b) = B.concat [beforePixel, pixel, afterPixel]
 where
 beforePixel = B.take before image
 afterPixel = B.drop (before+3) image
 pixel=B.pack [(fromIntegral r),(fromIntegral
 g),(fromIntegral b)]
 -- number of bytes before the 3 bytes of
 -- the pixel at x y
 before = (y * width * 3) + (x * 3) - 3

 main = do
 putStrLn P6
 putStrLn ( (show width) ++   ++ (show height) )
 putStrLn 255
 -- Set a red pixel at 100 100
 B.putStr (setPixel blankImage 100 100 (255,0,0))


 Can I please have some review comments on the code above? Would recreating
 the entire ByteString for each setPixel be an overhead?
 Also, I am barely beginning to grasp the Monad conceptI was wondering
 if there could be a monadic style of implementation of this - that could
 potentially have a series of setPixels inside a do block?

 Regards,
 Kashyap


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



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


Re: [Haskell-cafe] Re: Parsec lookahead and |

2009-08-20 Thread Job Vranish
try works in this case, but it won't if we are using a parser which can
consume and then fail (instead of char 'a'). In which case we may want it to
fail without exploring the second option.

Hmmm though you might be right. Having lookAhead return Consumed is only a
problem if the parser passed to lookAhead succeeds, but the parser following
lookAhead fails without consuming, which seems like a fairly rare case.

Although, it would be a problem for cases where the lookAhead is checking
for a negation.  For example:
parseStuff = (lookAhead parseNotCapital  identifier) | number
wouldn't work if lookAhead returned Consumed on success, and try doesn't
save us either.

Even if returning Consumed is the desired behavior I'd still say it at
least deserves a note in the docs.

Martijn, how did you encounter this problem?

- Job


On Thu, Aug 20, 2009 at 2:21 PM, Christian Maeder
christian.mae...@dfki.dewrote:

 Daniel Fischer wrote:
  Am Donnerstag 20 August 2009 13:44:15 schrieb Martijn van Steenbergen:
  Goedemiddag café,
 
  Consider the following function, using parsec-3.0.0:
  la :: Parsec String () (Maybe Char)
  la = lookAhead (optionMaybe anyChar)
  *Lookahead parseTest (char 'a' | char 'b') a
  'a'
  *Lookahead parseTest (char 'a' | char 'b') b
  'b'
  *Lookahead parseTest (la * char 'a' | char 'b') a
  'a'
  *Lookahead parseTest (la * char 'a' | char 'b') b
  parse error at (line 1, column 2):
  unexpected b
  expecting a
 
  The first three work fine and as expected, but the fourth example fails
  where I would expect success. I know | won't try the rhs if the lhs
  consumed input, but lookAhead's documentation promises not to consume
  any input. Is this a bug in Parsec or am I missing something?
 
  Bad bug in Parsec (from the beginning, the same happens in parsec-2), I'd
 say.

 I'd say, its a feature. lookAhead returns whatever its argument returns.
  So in this case it returns Consumed without consuming.

 You can always wrap around a try to force the alternative:

  parseTest (try (la  char 'a') | char 'b') b

 Cheers Christian

 Maybe it should have been:

  la  (char 'a' | char 'b')

 in the first place.
 ___
 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


  1   2   >