Re: [Haskell-cafe] -- comments

2009-12-12 Thread Raynor Vliegendhart
On Sat, Dec 12, 2009 at 5:34 AM, Brandon S. Allbery KF8NH
allb...@ece.cmu.edu wrote:

  On Dec 11, 2009, at 23:30 , michael rice wrote:
 
  I'm just noticing that -- comments don't seem to work properly when the 
  first character following them is a '*'.

 I believe the spec only treats --  as a comment leader; this is why Haddock 
 markup has a space between the -- and the markup.

The spec [1] treats anything that starts with two or more dashes not
followed by a non-symbol to be the start of a comment.


[1] http://www.haskell.org/onlinereport/syntax-iso.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] accessible layout proposal?

2009-09-22 Thread Raynor Vliegendhart
On Tue, Sep 22, 2009 at 10:01 AM, Jimmy Hartzell j...@shareyourgifts.net 
wrote:
 I am in love with this proposal:
 http://www.haskell.org/haskellwiki/Accessible_layout_proposal

I'm not sure whether I like the idea in general or not. It looks a bit
odd. The suggestion on the talk page (
http://www.haskell.org/haskellwiki/Talk:Accessible_layout_proposal )
might be preferable, although I wonder about the implications. For
example, what should (#) be parsed as?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Mapping over multiple values of a list at once?

2009-08-27 Thread Raynor Vliegendhart
Just wondering, what should be the expected output be of something
like mavg 4 [1..3]? [3%2] or []?
Patai's and Eugene's solutions assume the former.

On Thu, Aug 27, 2009 at 10:19 AM, hask...@kudling.de wrote:
 Hi,

 Imagine you have a list with n-values. You are asked to iterate over the list 
 and calculate the average value of each 3 neighbouring values.

 For example, starting from

 [4,3,2,6,7]

 you need to find the averages of

 4,3,2 and 3,2,6 and 2,6,7

 resulting in

 [3,4,5]

 What is the most elegant way to do that?
 The naive ansatz to use (!!) excessively sounds pretty inefficient.

 Bye,
 Lenny
 ___
 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] A mistake in haskellwiki

2009-08-06 Thread Raynor Vliegendhart
On 8/6/09, Don Stewart d...@galois.com wrote:
 leaveye.guo:
  Hi haskellers:
 
  There is a mistake in http://www.haskell.org/haskellwiki/State_Monad
 
  It post two functions like this :
 
evalState :: State s a - s - a
evalState act = fst $ runState act
 
execState :: State s a - s - s
execState act = snd $ runState act
 
  Both the '$' operators should be '.'.
 
  Anyone would correct it ?

Fixed :)

 Well, it's a wiki ... :-)

 -- Don

That might be true, but not everyone has an account :)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: excercise - a completely lazy sorting algorithm

2009-07-12 Thread Raynor Vliegendhart
On 7/9/09, Heinrich Apfelmus apfel...@quantentunnel.de wrote:

 Of course, some part of algorithm has to be recursive, but this can be
 outsourced to a general recursion scheme, like the hylomorphism

hylo :: Functor f = (a - f a) - (f b - b) - (a - b)
hylo f g = g . fmap (hylo f g) . f


Is that definition of hylo actually usuable? A few on IRC tried to use
that definition for a few examples, but the examples failed to
terminate or blew up the stack.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Hylomorphisms (was: [Haskell-cafe] excercise - a completely lazy sorting algorithm)

2009-07-12 Thread Raynor Vliegendhart
On 7/12/09, Heinrich Apfelmus apfel...@quantentunnel.de wrote:
 Raynor Vliegendhart wrote:
  On 7/9/09, Heinrich Apfelmus apfel...@quantentunnel.de wrote:
  Of course, some part of algorithm has to be recursive, but this can be
  outsourced to a general recursion scheme, like the hylomorphism
 
 hylo :: Functor f = (a - f a) - (f b - b) - (a - b)
 hylo f g = g . fmap (hylo f g) . f
 
 
  Is that definition of hylo actually usable? A few on IRC tried to use
  that definition for a few examples, but the examples failed to
  terminate or blew up the stack.

 The implementation of  quicksort  with  hylo  works fine for me, given
 medium sized inputs like for example  quicksort (reverse [1..1000]) .

 What were the examples you tried?


One of the examples I tried was:

   hylo (unfoldr (\a - Just (a,a))) head $ 42

This expression fails to determinate.

Here are two examples copumpkin tried on IRC:

copumpkin  let hylo f g = g . fmap (hylo f g) . f  in hylo (flip
replicate 2) length 5
lambdabot   5

copumpkin  let hylo f g = g . fmap (hylo f g) . f  in hylo (flip
replicate 2) sum 5
lambdabot   * Exception: stack overflow
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monoid wants a (++) equivalent

2009-07-01 Thread Raynor Vliegendhart
On Tue, Jun 30, 2009 at 6:45 PM, Bryan O'Sullivanb...@serpentine.com wrote:
 I've thought for a while that it would be very nice indeed if the Monoid
 class had a more concise operator for infix appending than a `mappend` b.
 I wonder if other people are of a similar opinion, and if so, whether this
 is worth submitting a libraries@ proposal over.



We could use (Control.Category..) as an operator, but this would
require an additional wrapping layer if we wish to use the existing
Monoid instances:

 import Prelude hiding (id, (.))
 import Control.Category
 import Data.Monoid

 -- Category wrapper for existing Monoid instances
 newtype MonoidC m a b = MonoidC {unwrapMC :: m} deriving (Show)

 instance Monoid m = Category (MonoidC m) where
 id = MonoidC mempty
 MonoidC m . MonoidC n = MonoidC $ m `mappend` n

Furthermore, writing Category instances for monoids require dummy type
parameters:

 -- Example instance
 newtype SumC m a b = SumC {getSumC :: m} deriving (Show, Eq)

 instance Num a = Category (SumC a) where
 id = SumC (fromIntegral 0)
 SumC x . SumC y = SumC $ x + y

Another disadvantage of this approach is that we cannot have a default
monoid instance for lists (kind mismatch).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Obscure weirdness

2009-06-21 Thread Raynor Vliegendhart
On 6/20/09, Andrew Coppin andrewcop...@btinternet.com wrote:

 Is this a known bug in GHC 6.10.1? Will upgrading fix it? (Obviously, it's
 quite a lot of work to change GHC.) Suffice it to say that my program is
 quite big and complicated; it worked fine when it was still small and
 simple. ;-)

There is a bug in ghci 6.10.1 that seems to be fixed in 6.10.3 (not
sure whether it's fixed in 6.10.3). Certain non-terminating
expressions causes ghci to crash immediately and go back to the
prompt:


C:\ghci
GHCi, version 6.10.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
Prelude let loop = loop in loop

C:\


Compiling a module with a non-terminating expression first with ghc
and then loading it in ghci does not seem to result in a crash.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Maintaining laziness: another example

2009-06-08 Thread Raynor Vliegendhart
This might be slightly related. When I was assisting a Haskell lab
course, I encountered solutions like the following:

 removeRoot :: BSTree a - BSTree a
 removeRoot (Node x Empty Empty) = Empty
 removeRoot (Node x left  Empty) = left
 removeRoot (Node x Empty right) = right
 removeRoot (Node x left  right) = undefined {- not needed for discussion -}

The first removeRoot case is unnecessary. Students new to Haskell (or
maybe new to recursion in general?) seem to consider more base cases
than needed.


-Raynor


On 6/8/09, Martijn van Steenbergen mart...@van.steenbergen.nl wrote:
 Hello,

 While grading a Haskell student's work I ran into an example of a program
 not being lazy enough. Since it's such a basic and nice example I thought
 I'd share it with you:

 One part of the assignment was to define append :: [a] - [a] - [a],
 another to define cycle2 :: [a] - [a]. This was her (the majority of the
 students in this course is female!) solution:

  append :: [a] - [a] - [a]
  append [] ys = ys
  append xs [] = xs
  append (x:xs) ys = x : (append xs ys)
 
  cycle2 :: [a] - [a]
  cycle2 [] = error empty list
  cycle2 xs = append xs (cycle2 xs)
 

 This definition of append works fine on any non-bottom input (empty, finite,
 infinite), but due to the unnecessary second append case, cycle2 never
 produces any result.

 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] beginners question about fromMaybe

2009-06-02 Thread Raynor Vliegendhart
If you're absolutely certain that the lookup always succeeds, then you
can use pattern matching as follows:


   where
   jr  = joinTuples sc x val
   key = getPartialTuple is x
   Just val = Map.lookup key m



On 6/3/09, Nico Rolle nro...@web.de wrote:
 hi there

 heres a code snipped, don't care about the parameters.
 the thing is i make a lookup on my map m and then branch on that return 
 value

 probePhase is sc [] m = []
 probePhase is sc (x:xs) m
| val == Nothing  = probePhase is sc xs m
| otherwise   = jr ++ probePhase is sc xs m
where
jr  = joinTuples sc x (fromMaybe [] val)
key = getPartialTuple is x
val = Map.lookup key m


 the line jr  = joinTuples sc x (fromMaybe [] val) is kind of ugly
 because i know that it is not Nothing.
 is there a better way to solve this?
 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] beginners question about fromMaybe

2009-06-02 Thread Raynor Vliegendhart
I just noticed that my suggestion doesn't work. You're testing whether
val is Nothing and in my code snipped val has a different type.

On 6/3/09, Raynor Vliegendhart shinnon...@gmail.com wrote:
 If you're absolutely certain that the lookup always succeeds, then you
 can use pattern matching as follows:


   where
   jr  = joinTuples sc x val
   key = getPartialTuple is x
   Just val = Map.lookup key m



 On 6/3/09, Nico Rolle nro...@web.de wrote:
  hi there
 
  heres a code snipped, don't care about the parameters.
  the thing is i make a lookup on my map m and then branch on that return 
  value
 
  probePhase is sc [] m = []
  probePhase is sc (x:xs) m
 | val == Nothing  = probePhase is sc xs m
 | otherwise   = jr ++ probePhase is sc xs m
 where
 jr  = joinTuples sc x (fromMaybe [] val)
 key = getPartialTuple is x
 val = Map.lookup key m
 
 
  the line jr  = joinTuples sc x (fromMaybe [] val) is kind of ugly
  because i know that it is not Nothing.
  is there a better way to solve this?
  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] iota

2009-06-01 Thread Raynor Vliegendhart
The iota function you're looking for can be a whole lot simpler if you
know about monads (list monad in particular) and sequence. For lists,
sequence has the following behaviour:


sequence [xs1,xs2, ... xsn] =
   [[x1,x2, ... , xn] | x1 - xs1, x2 - xs2, ... , xn - xsn]


Using this, you can reduce your iota function to a powerful one-liner:

iota = sequence . map (enumFromTo 0 . pred)


Kind regards,

Raynor Vliegendhart


On 6/1/09, Paul Keir pk...@dcs.gla.ac.uk wrote:



 Hi all,



 I was looking for an APL-style “iota” function for array indices. I noticed

 “range” from Data.Ix which, with a zero for the lower bound (here (0,0)),

 gives the values I need:



  let (a,b) = (2,3)

  index ((0,0),(a-1,b-1))

  [(0,0),(0,1),(0,2),(1,0),(1,1),(1,2)]



 However, I need the results as a list of lists rather than a list of tuples;
 and

 my input is a list of integral values. I ended up writing the following
 function

 instead. The function isn’t long, but longer than I first expected. Did I
 miss a

 simpler approach?



 iota :: (Integral a) = [a] - [[a]]

 iota is = let count = product is

tups = zip (tail $ scanr (*) 1 is) is

buildRepList (r,i) = genericTake count $ cycle $


[0..i-1] = genericReplicate r

lists = map buildRepList tups

  in transpose lists



  length $ iota [2,3,4]

  24



 Thanks,

 Paul
 ___
 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