Beginners Digest, Vol 47, Issue 25

2012-05-28 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  Category question (Brent Yorgey)
   2. Re:  Category question (Manfred Lotz)
   3. Re:  problems with wxHaskell installation (Miguel Negrao)
   4. Re:  Category question (Jay Sulzberger)
   5. Re:  problems with wxHaskell installation (Heinrich Apfelmus)
   6.  How to solve this using State Monad? (kak dod)


--

Message: 1
Date: Mon, 28 May 2012 12:43:33 -0400
From: Brent Yorgey byor...@seas.upenn.edu
Subject: Re: [Haskell-beginners] Category question
To: beginners@haskell.org
Message-ID: 20120528164333.ga5...@seas.upenn.edu
Content-Type: text/plain; charset=us-ascii

On Mon, May 28, 2012 at 04:14:40PM +0200, Manfred Lotz wrote:
 
 For me id: A - A could be defined by: A morphism id: A - A is
 called identity morphism iff for all x of A we have  id(x) = x.

This is not actually a valid definition; the notation id(x) = x does
not make sense.  It seems you are assuming that morphisms represent
some sort of function, but that is only true in certain special
categories.

 My point is that in the books about category theory those two statements
 are stated as axioms, and id is (in many books) just self understood or
 defined as I have defined it above.
 
 If in a book about category the author would say that for each object A
 there must exist a morphism id: A - A (called identity morphism) which
 is defined by idB . f = f and f . idA = f then this would be clearer
 (and better, IMHO).

This is exactly what category theory books do (or should) say.  Do you
have a particular example of a book which does not state things in
this way?

Note that there is no particular difference between calling these
equations axioms or a definition.  That is, there is an 'identity
morphism' satisfying the following axioms... and there is an
'identity morphism' defined by... are just two different ways of
saying the exact same thing.

-Brent



--

Message: 2
Date: Mon, 28 May 2012 18:50:34 +0200
From: Manfred Lotz manfred.l...@arcor.de
Subject: Re: [Haskell-beginners] Category question
To: beginners@haskell.org
Message-ID: 20120528185034.51ed2...@arcor.com
Content-Type: text/plain; charset=US-ASCII

On Mon, 28 May 2012 10:57:11 -0400
Brent Yorgey byor...@seas.upenn.edu wrote:

 On Mon, May 28, 2012 at 04:14:40PM +0200, Manfred Lotz wrote:
  
  For me id: A - A could be defined by: A morphism id: A - A is
  called identity morphism iff for all x of A we have  id(x) = x.
 
 This is not actually a valid definition; the notation id(x) = x does
 not make sense.  It seems you are assuming that morphisms represent
 some sort of function, but that is only true in certain special
 categories.
 

Ok, it is a valid definition only in a certain context. In the
far wider context of category theory this indeed makes no sense.



  My point is that in the books about category theory those two
  statements are stated as axioms, and id is (in many books) just
  self understood or defined as I have defined it above.
  
  If in a book about category the author would say that for each
  object A there must exist a morphism id: A - A (called identity
  morphism) which is defined by idB . f = f and f . idA = f then this
  would be clearer (and better, IMHO).
 
 This is exactly what category theory books do (or should) say.  Do you
 have a particular example of a book which does not state things in
 this way?
 

In 'Conceptual Mathematics' by F. William Lawvere, Stephen H. Schanuel
they define an identity map with fa = a for each a in A.
Then on page 17 they define category and say 

...
Identity Maps: (one per object) 1A: A - A
...
Rules for a category
1. The identity laws:
where they say g . 1A = g and 1B . f = f
2. associatlve laws
...

It seems that this definition of a category is not as general as it
could be. Here 1. is something which follows easily from the definition
of an identity map.


I guess that this made me think of idA as idA(x) = x for each x of A.
Later when I saw other (more general) definitions I did not read
carefully to realize the difference.


Thanks a lot for making this clear to me.


-- 
Manfred





--

Message: 3
Date: Mon, 28 May 2012 18:31:08 +0100
From: Miguel Negrao miguel.negrao-li...@friendlyvirus.org
Subject: Re: [Haskell-beginners] problems with wxHaskell installation
To: beginners@haskell.org
Message-ID: 31f41061-3886-4356-a3d1-6ed3499a1...@friendlyvirus.org
Content-Type: text/plain; 

Beginners Digest, Vol 47, Issue 26

2012-05-28 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  problems with wxHaskell installation (Miguel Negrao)
   2. Re:  problems with wxHaskell installation (Brandon Allbery)
   3. Re:  How to solve this using State Monad? (Ertugrul S?ylemez)
   4. Re:  problems with wxHaskell installation (Miguel Negrao)
   5. Re:  How to solve this using State Monad? (Ozgur Akgun)
   6.  State and GUI's / external interfaces / events (Henry Lockyer)


--

Message: 1
Date: Mon, 28 May 2012 20:20:21 +0100
From: Miguel Negrao miguel.negrao-li...@friendlyvirus.org
Subject: Re: [Haskell-beginners] problems with wxHaskell installation
To: beginners@haskell.org
Message-ID: 8e5a9b9e-b6d9-441c-b9b8-76222be11...@friendlyvirus.org
Content-Type: text/plain; charset=windows-1252


A 28/05/2012, ?s 19:44, Heinrich Apfelmus escreveu:

 Miguel Negrao wrote:
 When I try to install wx after updating cabal it is failing on version 
 0.90..0.1:
 miguelnegrao@Mac-Miguel:~$ cabal install wx
 Resolving dependencies...
 Configuring wx-0.90.0.1...
 Preprocessing library wx-0.90.0.1...
 Building wx-0.90.0.1...
 [ 1 of 16] Compiling Graphics.UI.WX.Types ( src/Graphics/UI/WX/Types.hs, 
 dist/build/Graphics/UI/WX/Types.o )
 [ 2 of 16] Compiling Graphics.UI.WX.Attributes ( 
 src/Graphics/UI/WX/Attributes.hs, dist/build/Graphics/UI/WX/Attributes.o )
 [ 3 of 16] Compiling Graphics.UI.WX.Layout ( src/Graphics/UI/WX/Layout.hs, 
 dist/build/Graphics/UI/WX/Layout.o )
 [ 4 of 16] Compiling Graphics.UI.WX.Classes ( src/Graphics/UI/WX/Classes.hs, 
 dist/build/Graphics/UI/WX/Classes.o )
 [ 5 of 16] Compiling Graphics.UI.WX.Media ( src/Graphics/UI/WX/Media.hs, 
 dist/build/Graphics/UI/WX/Media.o )
 [ 6 of 16] Compiling Graphics.UI.WX.Events ( src/Graphics/UI/WX/Events.hs, 
 dist/build/Graphics/UI/WX/Events.o )
 [ 7 of 16] Compiling Graphics.UI.WX.Window ( src/Graphics/UI/WX/Window.hs, 
 dist/build/Graphics/UI/WX/Window.o )
 src/Graphics/UI/WX/Window.hs:134:52:
   Not in scope: `textCtrlChangeValue'
 cabal: Error: some packages failed to install:
 wx-0.90.0.1 failed during the building phase. The exception was:
 ExitFailure 1
 Does this mean that the package that was pushed to cabal has an
 actual  error ? How do I use the latest patch level releases? of the 
 packages ?
 
 Jeremy forgot to narrow the version dependencies of the family of wx 
 packages, not every combination that cabal accepts will actually work. The 
 effect is that you have to reinstall the packages in the right order and with 
 the right version number to get it to work. The following should do the trick
 
cabal install wxdirect-0.90.0.1
cabal install wxc-0.90.0.3
cabal install wxcore-0.90.0.1
cabal install wx-0.90.0.1
 
 The last number in the version number indicates bug fixes, that's why I refer 
 to it as patch-level?.

Ah, ok. I ran all those commands, but with --reinstall since some were already 
installed, in that order. Everything installed correctly.

Now when I try to compile a hello world program * I get :

ghc test.hs
[1 of 1] Compiling Main ( test.hs, test.o )
Linking test ...
ld: warning: ignoring file 
/System/Library/Frameworks//QuickTime.framework/QuickTime, file was built for 
unsupported file format which is not the architecture being linked (x86_64)
ld: warning: could not create compact unwind for _ffi_call_unix64: does not use 
RBP or RSP based frame
Undefined symbols for architecture x86_64:
  _wxListItemAttr_CreateEx, referenced from:
  _sUn6_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  _sUng_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  _wxListItemAttr_Create, referenced from:
  
_wxcorezm0zi90zi0zi1_GraphicsziUIziWXCoreziWxcClassesAL_listItemAttrCreate1_info
 in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  _wxListCtrlVirtual_CreateWithCb, referenced from:
  _sW0i_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  _sW0E_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  _wxListCtrlVirtual_Create, referenced from:
  _sWbY_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  _sWcg_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  _wxListItemAttr_SetTextColour, referenced from:
  _s15xV_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  _wxListItemAttr_SetFont, referenced from:
  _s15BK_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  _s15BO_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  _wxListItemAttr_SetBackgroundColour, referenced from:
  _s15Gu_info in 

Beginners Digest, Vol 47, Issue 28

2012-05-29 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  Category question (Manfred Lotz)
   2.  monad transformer show help (rickmurphy)
   3. Re:  monad transformer show help (Tobias Brandt)
   4. Re:  Category question (Brent Yorgey)
   5. Re:  Category question (Manfred Lotz)
   6. Re:  State and GUI's / external interfaces /  events
  (Henry Lockyer)


--

Message: 1
Date: Tue, 29 May 2012 13:42:39 +0200
From: Manfred Lotz manfred.l...@arcor.de
Subject: Re: [Haskell-beginners] Category question
To: beginners@haskell.org
Message-ID: 20120529134239.4a518...@arcor.com
Content-Type: text/plain; charset=US-ASCII

On Mon, 28 May 2012 13:43:33 -0400 (EDT)
Jay Sulzberger j...@panix.com wrote:


 
 No.  The point is that, by definition, a category, call it C, is
 a struct with two sets, Obj(C) and Mor(C), and further operations:
 
 1. head: Mor(C) - Obj(C)
 
 2. tail: Mor(C) - Obj(C)
 
 3. id: Obj(C) - Mor(C)
 
 4. *: Mor(C) x Mor(C) - Mor(C)
 
 where head and tail and id are everywhere defined single valued
 maps.  They are all maps of sets.  *, read composition of
 morphisms is a map of sets, with signature as displayed, but is
 not usually everywhere defined.  We have then several
 equational axioms, which C is required to satisfy to be a
 category.
 
 (set theoretical note: We have, partly implicitly, ruled out
 categories which are not small.  See standard texts for this
 locus of difficulty.)
 
 By the axioms, any object b of C must have defined its associated
 identity morphism id[b].  For many categories, b will always be
 an actual set, and id[b] will be the unique map of sets defined
 by
 
(id[b])(x) = x , for all x in b
 
 where (id[b])(x) is read the result of applying id[b] to the element
 x of b.
 
 But, as explained, many categories have objects which are not
 sets.  Indeed, often, no object is a set.
 
 The definition of category never mentions whether or not the
 objects are sets.  And, as we have seen, there are many
 categories whose objects are not sets.  (Perhaps categorically
 better: many categories are not directly presented as having
 objects which are sets.)
 
 to repeat: The concept category is larger in extension than the
 concept category whose objects are sets and whose morphisms are
 maps of sets.
 
 ad representations of categories:
 
http://en.wikipedia.org/wiki/Yoneda_Lemma
[page was last modified on 1 April 2012 at 05:17]
 
 
 
  I guess that this made me think of idA as idA(x) = x for each x of
  A. Later when I saw other (more general) definitions I did not read
  carefully to realize the difference.
 
 
  Thanks a lot for making this clear to me.
 
 
  -- 
  Manfred
 
 I will let stand my restatement of what you already know ;)
 
 oo--JS.
 

Thanks a lot for the detailed example and explanations. I will study
your post thoroughly.



-- 
Manfred





--

Message: 2
Date: Tue, 29 May 2012 08:35:29 -0400
From: rickmurphy r...@rickmurphy.org
Subject: [Haskell-beginners] monad transformer show help
To: beginners beginners@haskell.org
Message-ID: 1338294929.2302.20.camel@metho-laptop
Content-Type: text/plain; charset=UTF-8

Hello All:

Over the past few days I got my first exposure to monad transformers.

I worked through the sample below. 

The witness w displays IC 0 as expected, but even after providing the
instance of show for type O I a, witness w' causes ghci to display

No instance for (Num (I' a0))
  arising from a use of w'
Possible fix: add an instance declaration for (Num (I' a0))

Would someone be able to explain why after providing the instance of
show on O I a, w' does not print the expected result (OC (IC 0)) ?

BTW - You will notice the sample intentionally avoids the use of
deriving (Show) on newtype I.

--
Rick


{-# LANGUAGE NoMonomorphismRestriction, DatatypeContexts,
FlexibleContexts, FlexibleInstances #-}

module Main where

import Control.Monad
import Control.Monad.Trans.Class

snip

-- |A parameterized new type I representing an inner type with one
constructor IC   
newtype I a = IC a -- deriving (Show)

-- |Unwraps the value in the inner type 
unI (IC x) = x

-- |A monad instance on the inner type
instance Monad I where
 return = IC
 m = f = f (unI m)

instance Show a = Show (I a) where
 show (IC x) = IC  ++ show x

-- |Witness on inner type
w :: Num a = I a
w = (IC 0) = return . id

-- |A parameterized new type O m a representing an outer type with a
named constructor 

Beginners Digest, Vol 47, Issue 29

2012-05-30 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  Performance problem (Jefferson Andrade)
   2.   Performance problem (Rados?aw Szymczyszyn)


--

Message: 1
Date: Wed, 30 May 2012 02:03:32 -0300
From: Jefferson Andrade joandr...@gmail.com
Subject: [Haskell-beginners] Performance problem
To: beginners@haskell.org
Message-ID:
ca+u7k5gg7vr5_+we1hwonbjjpslcakb0snxtsr7qu51-utn...@mail.gmail.com
Content-Type: text/plain; charset=utf-8

Hi!

I have a basic knowledge about Haskell and I am trying to put this
knowledge to work with a few exercises. The one I am trying now is
basically the following.

1. I must read from the standard input a series of text lines. Each line
represents a command that must be performed. The possible commands are:
add id first-name last-name birth-date phone-number
del id
info id
query (key:value)+

2. Each command may or may not generate an output on the standard output
according to a series of conditions (if an entry with the same ID already
exists, if the id of a del does not exists, if the id of an info does not
exists). Also, the info and query command also generate output on the
normal working.

3. The program is working, I suppose, but when I submit it for testing and
ranking on spoj.pl I get a timeout. The maximum allowed time for this
problem is 6s.

My code is the following:

= Begin of source code =

-- Problem id: HASHADQI

import qualified Data.List as List
import qualified Data.IntMap as Map
import Data.Maybe

type Person = (String,String,String,String)
type IntPersonMap = Map.IntMap Person

main = do
  input - getContents
  seqAction Map.empty $ lines input

seqAction :: IntPersonMap - [String] - IO IntPersonMap
seqAction m [] = return m
seqAction m (l:ls) = do
  m' - doAction m l
  seqAction m' ls

doAction :: IntPersonMap - String - IO IntPersonMap
doAction m cmd = do
  case cmd of
'a':cs - doInsert m (words cmd)
'd':cs - doDelete m (words cmd)
'i':cs - doInfo m (words cmd)
'q':cs - doQuery m (words cmd)
[] - return m

doInsert :: IntPersonMap - [String] - IO IntPersonMap
doInsert m [_, idText, fn, ln, bd, pn] = do
  let id = read idText :: Int
  if Map.member id m
then do putStrLn $ ID  ++ show id ++  ja cadastrado.
return m
else return (Map.insert id (fn, ln, bd, pn) m)

doDelete :: IntPersonMap - [String] - IO IntPersonMap
doDelete m [_, idText] = do
  let id = read idText :: Int
  if Map.member id m
then return (Map.delete id m)
else do putStrLn $ ID  ++ show id ++  nao existente.
return m

doInfo :: IntPersonMap - [String] - IO IntPersonMap
doInfo m [_, idText] = do
  let id = read idText :: Int
  case Map.lookup id m of
Just (fn, ln, bd, pn) - do putStrLn $ unwords [fn, ln, bd, pn]
return m
Nothing - do putStrLn $ ID  ++ show id ++  nao existente.
  return m

doQuery :: IntPersonMap - [String] - IO IntPersonMap
doQuery m (_:qs) = do
  let test = (\x - foldl () True $ map ($x) $ makePredicate qs)
  result = Map.filter test m
  putStrLn $ unwords . map show $ Map.keys result
  return m

makePredicate :: [String] - [(Person - Bool)]
makePredicate [] = []
makePredicate (q:qs) =
  case List.break (==':') q of
(fn, ':':x) - (\(fn,_,_,_) - fn == x) : (makePredicate qs)
(ln, ':':x) - (\(_,ln,_,_) - ln == x) : (makePredicate qs)
(bd, ':':x) - (\(_,_,bd,_) - bd == x) : (makePredicate qs)
(pn, ':':x) - (\(_,_,_,pn) - pn == x) : (makePredicate qs)

= End of source code =

Can any one explain where is the source(s) of inefficiency and suggest how
to make this program more efficient?

Thanks in advance,
Jeff.
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120530/80fe29f1/attachment-0001.htm

--

Message: 2
Date: Wed, 30 May 2012 11:07:22 +0200
From: Rados?aw Szymczyszyn lav...@gmail.com
Subject: [Haskell-beginners]  Performance problem
To: beginners@haskell.org
Message-ID:
CAG=dco2ff0z83+g+tvhjrpw1uwu066zr4pa0y5-ga+ordvr...@mail.gmail.com
Content-Type: text/plain; charset=UTF-8

Hello!

I've had a similar problem with text processing discussed on the list
some time ago (a topic about implementing a spellchecker). To keep
things short'n'simple: built-in Haskell Strings are inefficient as
they're simply lists of Chars, i.e. a String is in fact just a [Char].

The usually suggested 

Beginners Digest, Vol 47, Issue 31

2012-05-30 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  How to solve this using State Monad? (Henry Lockyer)
   2. Re:  How to solve this using State Monad? (kak dod)


--

Message: 1
Date: Wed, 30 May 2012 16:14:35 +0100
From: Henry Lockyer henry.lock...@ntlworld.com
Subject: Re: [Haskell-beginners] How to solve this using State Monad?
To: beginners@haskell.org
Message-ID: 463edfbf-a1d5-4436-a37b-708e2a5e9...@ntlworld.com
Content-Type: text/plain; charset=us-ascii

I should have gone back and cleaned up my original 'Version 1' example so that 
both examples use exactly the same 'stateMC' function.
I have now made this small improvement below FWIW.  
/Henry

On 30 May 2012, at 15:31, Henry Lockyer wrote:

 Hi kak,
 
 On 28 May 2012, at 19:49, kak dod wrote:
 
 Hello,
 A very good morning to all.
 
 I am a Haskell beginner. And although I have written fairly complicated 
 programs and have understood to some extent the concepts like pattern 
 matching, folds, scans, list comprehensions, but I have not satisfactorily 
 understood the concept of Monads yet. I have partially understood and used 
 the Writer, List and Maybe monads but the State monad completely baffles me.
 
 I wanted to write a  program for the following problem: A DFA simulator. 
 This I guess is a right candidate for State monad as it mainly deals with 
 state changes.
 
 What the program is supposed to do is:
 
 . . . 
 
 I wrote a recursive program to do this without using any monads. I simply 
 send the entire dfa, the input string and its partial result in the 
 recursive calls.
 
 How to do this using State Monad?
 
 . . .
 
 Please note that I wish your solution to use the Control.Monad.State. 
 
 I coincidentally included something like this in another post I recently 
 made. 
 I have quickly tweaked my example slightly and added a complete alternative 
 example using the State monad below.
 Both programs now have the same external behaviour.
 It is a simpler example than the DFA that you are proposing. If I have time 
 I'll look at your specific version of 
 the problem, but I am assuming that your main aim here is to understand the 
 State monad better - rather than the DFA 
 exactly as you have specified it -  so perhaps the following simple examples 
 may help a little:
 
 ---
 --
 -- aha! 
 --
 -- An exciting game that requires the string aha! to
 -- be entered in order to reach the exit, rewarded with a *.
 --
 -- A simple state machine.
 --
 -- Version 1 - not using the State monad...
 --
 
 import System.IO
 
 type MyState = Char
 
 initstate, exitstate :: MyState
 initstate = 'a'
 exitstate = 'z'
 
 main = do hSetBuffering stdin NoBuffering -- (just so it responds char by 
 char on the terminal)
   stateIO initstate
  
 stateIO :: MyState - IO ()
 stateIO s = do c_in - getChar
   let (str_out, s') = stateMC' c_in s
   putStr str_out  -- (newline flushes the output)
 stateIO s' 
 
-- now uses exactly the same stateMC func as in version 2 below...
-- ('Y' = Yes, 'N' = No, '*' = congratulations game over, blank responses after 
game over)

stateMC' :: Char - MyState - (String, MyState)
stateMC' 'a' 'a' = ( Y\n, 'b')
stateMC' 'h' 'b' = ( Y\n, 'c')
stateMC' 'a' 'c' = ( Y\n, 'd')
stateMC' '!' 'd' = ( *\n, 'z')
stateMC'  _  'z' = (  \n, 'z')
stateMC'  _   _  = ( N\n, 'a')


 
 
 
 
 --
 -- Version 2 - using the State monad...
 -- This time it treats the input as one long lazy String of chars 
 -- rather than char-by-char reading as in version 1
 -- 
 
 import System.IO
 import Control.Monad.State
 
 type MyState = Char
 
 initstate, exitstate :: MyState
 initstate = 'a'
 exitstate = 'z'
  
 main = do hSetBuffering stdin NoBuffering 
   interact mystatemachine  
 
 mystatemachine :: String - String
 mystatemachine str = concat $ evalState ( mapM charfunc str ) initstate
 
 charfunc :: Char - State MyState String
 charfunc c = state $ stateMC' c -- wrap the stateMC' func in the state 
 monad

snip - remove previous comment

 stateMC' :: Char - MyState - (String, MyState)
 stateMC' 'a' 'a' = ( Y\n, 'b')
 stateMC' 'h' 'b' = ( Y\n, 'c')
 stateMC' 'a' 'c' = ( Y\n, 'd')
 stateMC' '!' 'd' = ( *\n, 'z')
 stateMC'  _  'z' = (  \n, 'z')
 stateMC'  _   _  = ( N\n, 'a')
 
 -
 
 Advantages of using 

Beginners Digest, Vol 47, Issue 33

2012-05-31 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  How to solve this using State Monad? (Henry Lockyer)
   2. Re:  How to solve this using State Monad? (Ertugrul S?ylemez)
   3. Re:  How to solve this using State Monad? (Michael Alan Dorman)


--

Message: 1
Date: Thu, 31 May 2012 11:58:47 +0100
From: Henry Lockyer henry.lock...@ntlworld.com
Subject: Re: [Haskell-beginners] How to solve this using State Monad?
To: kak dod kak.dod2...@gmail.com
Cc: beginners@haskell.org, Ertugrul S?ylemez e...@ertes.de
Message-ID: a38a2cbe-70dd-4832-a021-c44f11574...@ntlworld.com
Content-Type: text/plain; charset=iso-8859-1

Hi kak - ok, my mistake - I interpreted your candidate for the state monad, 
and Please note that I wish your solution to use the Control.Monad.State 
too literally.  Arrows may point the way forward for you then ;-)   

I have a suspicion that if the State monad doesn't make sense yet, then Arrows 
will not be more obvious,  
they look like a kind of more generalised monadic structure (though I don't 
understand them myself yet) 
- but maybe a better fit to your problem will in fact make them clearer for you.

Regarding the State monad: I think it may be slightly unfortunate that it gets 
introduced as THE state monad (I guess Ertugrul may
agree here...) and the initial examples, like the favourite random number 
generation example, do not make it immediately obvious how 
you might apply it more widely.  I certainly experienced a little 
head-scratching before realising I could simply use things like  
charfunc c = state (stateMC c).
Another thing that can cause some initial confusion is the fact that the 
standard implementation seems to have changed since some of the
educational texts were written, so you may find yourself in Hoogle looking at 
monad transformers before you feel quite ready for them ;-) 
Also the standard solution does not export the value constructor so, unlike 
some examples that you may see, you can only use State for 
type definitions and you need to use state to create an actual value.   I 
think it is a good idea, as Ertugrul suggested, to write your 
own state monad instance, and it avoids these 'noise factors' from the library 
implem. 
/Henry

On 31 May 2012, at 05:29, kak dod wrote:

 Hello Ertugrul,
 
 Thank you very much for your patience with a stupid like me. I am going 
 through your comments, part of it is going parallel but I am getting 
 something. Sorry for that.
 
 But I am bit confused with the purpose of State Monad now. Is the name State 
 Monad appropriate to this monad?
 I mean, if it is appropriate then the State Monad must be useful to model all 
 types of computations involving state as a dominant part. Am I making a 
 mistake here? I guess, I am.
 
 Because it seems from what you have said that the State Monad is appropriate 
 only for some types of computations involving state and not appropriate for 
 something like DFA which I think is a stateful computation.
 
 What I am trying to do is write a Turing Machine simulator in Haskell? It's 
 also mainly a state change thing, so if Ertugrul says that State Monad is not 
 suitable for DFA simulation, it won't be suitable for TM simulation either.
 
 So, exactly what type of computations involving what type of states are 
 better handled by the State Monad? 
 I mean what type of state-computations can be made composible using  the 
 State Monad and what type of  state-computations cannot be made  composible 
 using  the State Monad? (As you have pointed out automaton cannot be made 
 composible using the State Monad in an elegant manner.)  
 
 Thanks Henry for your example, it has helped me a lot.
 
 
 On Thu, May 31, 2012 at 6:12 AM, Henry Lockyer henry.lock...@ntlworld.com 
 wrote:
 I hear you Ertugrul ;-)
 
 I interpret that kak is struggling to understand the State monad, not find 
 the best solution for a DFA,
 so telling him about something else which is not the State monad will 
 probably not help him too much
 at this point...
 
 Your propaganda is working on me though ! :-)
 I haven't looked at the arrows area at all so far, but I'm interested in 
 state handling solutions
 so I see I need to move it up my reading list!
 Thanks/ Henry
 
 On 30 May 2012, at 23:25, Ertugrul S?ylemez wrote:
 
  Again to promote the automaton arrow, Henry's aha! DFA in the
  automaton arrow:
 
 aha :: Auto Char Char
 aha = aha' 0
 where
 aha' :: Int - Auto Char Char
 

Beginners Digest, Vol 47, Issue 34

2012-05-31 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  How to solve this using State Monad? (Miguel Negrao)
   2. Re:  How to solve this using State Monad? (Ertugrul S?ylemez)
   3. Re:  How to solve this using State Monad? (Henry Lockyer)
   4.  GHCi won't allow type declaration as shown inLYAHFGG (Stan Kulp)
   5. Re:  GHCi won't allow type declaration as shown   in LYAHFGG
  (Homero Cardoso de Almeida)
   6. Re:  GHCi won't allow type declaration as shown   in LYAHFGG
  (Brandon Allbery)


--

Message: 1
Date: Thu, 31 May 2012 16:46:26 +0100
From: Miguel Negrao miguel.negrao-li...@friendlyvirus.org
Subject: Re: [Haskell-beginners] How to solve this using State Monad?
To: beginners@haskell.org
Message-ID: 9c2c6f14-1233-49cc-a346-b48140a6d...@friendlyvirus.org
Content-Type: text/plain; charset=windows-1252


A 31/05/2012, ?s 16:25, Michael Alan Dorman escreveu:

 Ertugrul S?ylemez e...@ertes.de writes:
 I almost feel stupid writing these long explanations, just to see them
 getting ignored ultimately.  The automaton arrow is one of the most
 useful and most underappreciated concepts for state in Haskell.
 
 While I'm not sure I have a need for it right now, I definitely haven't
 ignored this exchange---I've read the individual emails, and a link to
 the archive is filed away for future use.
 
 So it's been very helpful, even if those being helped aren't
 participating per se.

+1

Because of those posts I spent my morning reading about arrows which seems a 
quite interesting concept, although couldn?t yet see what is best for ( I would 
be curious to learn it in order to try out Yampa).  I have to say that the 
resources I found to learn about arrows on the net were a bit disorganized. 
This page is really well done  
http://en.wikibooks.org/wiki/Haskell/Understanding_arrows but then because I 
don?t know much about parsers I couldn?t really progress through the second 
half.

best,
Miguel Negr?o


--

Message: 2
Date: Thu, 31 May 2012 18:18:07 +0200
From: Ertugrul S?ylemez e...@ertes.de
Subject: Re: [Haskell-beginners] How to solve this using State Monad?
To: beginners@haskell.org
Message-ID: 20120531181807.37bed...@tritium.streitmacht.eu
Content-Type: text/plain; charset=utf-8

Miguel Negrao miguel.negrao-li...@friendlyvirus.org wrote:

 Because of those posts I spent my morning reading about arrows which
 seems a quite interesting concept, although couldn?t yet see what is
 best for ( I would be curious to learn it in order to try out Yampa).
 I have to say that the resources I found to learn about arrows on the
 net were a bit disorganized. This page is really well done
 http://en.wikibooks.org/wiki/Haskell/Understanding_arrows but then
 because I don?t know much about parsers I couldn?t really progress
 through the second half.

I have started an arrow tutorial which many people found easy to follow.
It's not finished yet, but since so many people found it useful I'm
sharing that unfinished tutorial:

http://ertes.de/new/tutorials/arrows.html

It answers the most important questions:  What?  Why?  How?  To some
extent it also answers:  When?  But I have to work on that question.
The basics of the automaton arrow are covered, but when I find time I
will extend the tutorial to cover Auto in full.  Finally I also intend
to cover a powerful generalization of Auto:  the wire arrow, which is
the basis of the Netwire AFRP library.


Greets,
Ertugrul

-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/
-- next part --
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 836 bytes
Desc: not available
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120531/709e5178/attachment-0001.pgp

--

Message: 3
Date: Thu, 31 May 2012 17:23:08 +0100
From: Henry Lockyer henry.lock...@ntlworld.com
Subject: Re: [Haskell-beginners] How to solve this using State Monad?
To: beginners@haskell.org
Message-ID: 41b1172f-bfa0-450e-adf9-b74fe4adf...@ntlworld.com
Content-Type: text/plain; charset=windows-1252

+ I think I already said it, but, in case it was not clear: Me too.
 Even as a participating person I feel helped!  ;-)
I just haven't taken it onboard yet and need that quiet free morning
to read more about it...

+ I think this is clearly identifying the point where the State monad(s) 
can become confusing at first, in my (limited) experience:

Beginners Digest, Vol 48, Issue 1

2012-06-01 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  GHCi won't allow type declaration as shown   in LYAHFGG
  (Keshav Kini)
   2. Re:  GHCi won't allow type declaration as shown   in LYAHFGG
  (Homero Cardoso de Almeida)
   3. Re:  How to solve this using State Monad? (Rustom Mody)


--

Message: 1
Date: Thu, 31 May 2012 14:16:04 -0700
From: Keshav Kini keshav.k...@gmail.com
Subject: Re: [Haskell-beginners] GHCi won't allow type declaration as
shown   in LYAHFGG
To: beginners@haskell.org
Message-ID: 86r4u09hm3@zhenghe.ntu.edu.sg
Content-Type: text/plain; charset=us-ascii

Stan Kulp stan_k...@yahoo.com writes:
 I have been working my way through Learn You a Haskell for Greater Good and
 am stumped when I get to the Syntax in Functions - Pattern Matching section.

 The book shows the following expression...

 ghci lucky :: (Integral a) = a - String  

As far as I can see, the live version of `the section you mention`_ on
learnyouahaskell.com does not contain this text - it doesn't have the
ghci  at the beginning of the line. Besides what others have said in
response to your question, I would add that you should make sure to read
LYAH on the website if possible - other sources might be out of date, as
I think the author does update the website version from time to time.

.. _the section you mention:
   http://learnyouahaskell.com/syntax-in-functions#pattern-matching

-Keshav




--

Message: 2
Date: Thu, 31 May 2012 19:45:56 -0300
From: Homero Cardoso de Almeida homero...@gmail.com
Subject: Re: [Haskell-beginners] GHCi won't allow type declaration as
shown   in LYAHFGG
To: Keshav Kini keshav.k...@gmail.com
Cc: beginners@haskell.org
Message-ID:
capv0zwq_sw2lx+dndv3osm8ijjopqzcgk9s4w8yfwdpbi86...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

I just tried here, and got no problems.

lucky.hs:
lucky :: (Integral a) = a - String
lucky 7 = LUCKY NUMBER SEVEN!!!
lucky x = Sorry, you're out of luck, pal...

ghci:
:load /path/to/lucky.hs
[1 of 1] Compiling Main ( /path/to/lucky.hs, interpreted )
Ok, modules loaded: Main.
*Main lucky 7
LUCKY NUMBER SEVEN!!!
*Main lucky 200
Sorry, you're out of luck, pal...
*Main

I would suggest verifying my ghc installation or for any funky chars in
the file.

Homero Cardoso de Almeida

On Thu, May 31, 2012 at 6:16 PM, Keshav Kini keshav.k...@gmail.com wrote:

 Stan Kulp stan_k...@yahoo.com writes:
  I have been working my way through Learn You a Haskell for Greater
 Good and
  am stumped when I get to the Syntax in Functions - Pattern Matching
 section.
 
  The book shows the following expression...
 
  ghci lucky :: (Integral a) = a - String

 As far as I can see, the live version of `the section you mention`_ on
 learnyouahaskell.com does not contain this text - it doesn't have the
 ghci  at the beginning of the line. Besides what others have said in
 response to your question, I would add that you should make sure to read
 LYAH on the website if possible - other sources might be out of date, as
 I think the author does update the website version from time to time.

 .. _the section you mention:
   http://learnyouahaskell.com/syntax-in-functions#pattern-matching

 -Keshav


 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners

-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120531/97815794/attachment-0001.htm

--

Message: 3
Date: Fri, 1 Jun 2012 08:58:01 +0530
From: Rustom Mody rustompm...@gmail.com
Subject: Re: [Haskell-beginners] How to solve this using State Monad?
To: Ertugrul S?ylemez e...@ertes.de
Cc: beginners@haskell.org
Message-ID:
caj+teof7fz-tmoctfxcpknep54+i96+fwjtcsxzi47ppyq4...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

On Thu, May 31, 2012 at 9:48 PM, Ertugrul S?ylemez e...@ertes.de wrote:


 I have started an arrow tutorial which many people found easy to follow.
 It's not finished yet, but since so many people found it useful I'm
 sharing that unfinished tutorial:

http://ertes.de/new/tutorials/arrows.html

 It answers the most important questions:  What?  Why?  How?  To some
 extent it also answers:  When?  But I have to work on that question.



Hi Ertugrul,

As usual this is useful and I'll be studying it in more 

Beginners Digest, Vol 48, Issue 5

2012-06-05 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  attoparsec and EOF (Arthur Clune)
   2. Re:  attoparsec and EOF (Arthur Clune)
   3. Re:  histogram over large data (Rados?aw Szymczyszyn)
   4. Re:  histogram over large data (Stephen Tetley)
   5. Re:  histogram over large data (Ian Knopke)
   6.  graphics.gloss errors (Gregory Guthrie)
   7.  wxHaskell install errors (Gregory Guthrie)
   8. Re:  graphics.gloss errors (Brent Yorgey)
   9. Re:  graphics.gloss errors (Gregory Guthrie)
  10. Re:  histogram over large data (Stephen Tetley)


--

Message: 1
Date: Tue, 5 Jun 2012 15:29:03 +0100
From: Arthur Clune art...@clune.org
Subject: Re: [Haskell-beginners] attoparsec and EOF
To: beginners@haskell.org
Message-ID:
CAAa4kjx1T=oMqhFL+a4vzxR61nUea0ETWP+iyX=ozkqnj8o...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

And to answer my own question.I should use parseOnly.

--
Arthur Clune art...@clune.org


On Tue, Jun 5, 2012 at 10:56 AM, Arthur Clune art...@clune.org wrote:
 I'm writing a simple attoparsec parser, which works fine except for
 handling end of file:



--

Message: 2
Date: Tue, 5 Jun 2012 15:42:55 +0100
From: Arthur Clune art...@clune.org
Subject: Re: [Haskell-beginners] attoparsec and EOF
To: beginners@haskell.org
Message-ID:
CAAa4kjw0UpB9SFDfGWThaQRPbVW-w7obELuY=qe=dkiubfr...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

And to answer my own question.I should use parseOnly.

--
Arthur Clune art...@clune.org


On Tue, Jun 5, 2012 at 10:56 AM, Arthur Clune art...@clune.org wrote:
 I'm writing a simple attoparsec parser, which works fine except for
 handling end of file:



--

Message: 3
Date: Tue, 5 Jun 2012 20:41:42 +0200
From: Rados?aw Szymczyszyn lav...@gmail.com
Subject: Re: [Haskell-beginners] histogram over large data
To: beginners@haskell.org
Message-ID:
CAG=dco3qq++adaxfrytifr0r5qfesc3gsjhghiefzabsheu...@mail.gmail.com
Content-Type: text/plain; charset=UTF-8

Hi Ian,

In case you were looking for an example to get your teeth into you
might be interested in these: https://gist.github.com/287

These two scripts both serve the same purpose of building a map of
word counts from a text file. They both use Data.Text for Unicode IO,
but each tests a different structure. Though unordered-containers
package with its Data.HashMap is often suggested as an efficient
mapping structure, in my case (of these two scripts) the
Data.HashTable from standard library wins taking circa half the time
to run on the same dataset (though it's not purely functional as its
actions operate in the IO monad).

Finally, what puzzles me the most, is that a roughly equivalent script
in Python which just reads the same datafile into a standard dict
performs in about 1/3 of the time of the faster one of the above two
and Python's hardly a fast language... Bewildering, indeed.

Hope I didn't put you off :)



--

Message: 4
Date: Tue, 5 Jun 2012 21:06:00 +0100
From: Stephen Tetley stephen.tet...@gmail.com
Subject: Re: [Haskell-beginners] histogram over large data
To: Rados?aw Szymczyszyn lav...@gmail.com
Cc: beginners@haskell.org
Message-ID:
CAB2TPRBR9c5b3X5K7aaaHp5sOgJ8TZUeEnkmqSjU83zmJ2f=l...@mail.gmail.com
Content-Type: text/plain; charset=UTF-8

On 5 June 2012 19:41, Rados?aw Szymczyszyn lav...@gmail.com wrote:


 Finally, what puzzles me the most, is that a roughly equivalent script
 in Python which just reads the same datafile into a standard dict
 performs in about 1/3 of the time of the faster one of the above two
 and Python's hardly a fast language... Bewildering, indeed.

Dicts are efficient in Python though (as they are efficiently
implemented in C). Python often seems to beat Haskell in
micro-benchmarks that just fill a dictionary then run a simple query /
summation on it.



--

Message: 5
Date: Tue, 5 Jun 2012 21:09:49 +0100
From: Ian Knopke ian.kno...@gmail.com
Subject: Re: [Haskell-beginners] histogram over large data
To: Stephen Tetley stephen.tet...@gmail.com
Cc: beginners@haskell.org
Message-ID:
cac+f4wmk3kovxddjqth79w8diftaqufm3azovlnxmk25pme...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

Hi Stephen,

I see now I didn't explain myself especially well. One way to build a
frequency count in haskell comes from LYAHFGG, chapter 7:

ghci map (\l@(x:xs) - (x,length l)) . group . 

Beginners Digest, Vol 48, Issue 7

2012-06-06 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  flatten comma operator (Arlen Cuss)
   2. Re:  wrapping text in a multiline string (Rico Moorman)
   3. Re:  flatten comma operator (Kees Bleijenberg)
   4. Re:  wrapping text in a multiline string (Arlen Cuss)
   5. Re:  wxHaskell path (Miguel Negrao)


--

Message: 1
Date: Wed, 6 Jun 2012 16:42:52 +1000
From: Arlen Cuss a...@unnali.com
Subject: Re: [Haskell-beginners] flatten comma operator
To: Kees Bleijenberg k.bleijenb...@inter.nl.net
Cc: beginners@haskell.org
Message-ID: bd4727d194e842a39621f06d81389...@unnali.com
Content-Type: text/plain; charset=utf-8

By the way, is the excerpt from RWH involving liftA2 the chapter on using 
Parsec? If so, this may be the code snippet you refer to:

-- file: ch16/FormApp.hs a_pair :: CharParser () (String, Maybe String) a_pair 
= liftA2 (,) (many1 a_char) (optionMaybe (char '=' * many a_char))

In this case, liftA2 is promoting the (,) operation to work with the two 
operations in the CharParser applicative functor.

(,) is of type a - b - (a,b), so without lifting, we'd end up with 
something like (CharParser () String, CharParser () Maybe String) (just a 
guess here).

liftA2 produces a new applicative functor action which computes each of (many1 
a_char) and (optionMaybe (char '=' * many a_char)), then gives the pure 
results to (,). 


On Wednesday, 6 June 2012 at 4:36 PM, Arlen Cuss wrote:

 If (,) is a function that takes two elements and returns the 2-tuple, have 
 you considered something like (,,)? :)
 
 
 
 On Wednesday, 6 June 2012 at 4:33 PM, Kees Bleijenberg wrote:
 
  In 'Real World Haskell' I found code like LiftA2 (,) 
  Looks odd. But after some experimenting in winghci I found that (,) 1 2 is 
  valid code and is equal to (1,2).
  Now I wonder how to create (1,2,3). I think you need a join or a flatten 
  function or ...? Join doesn't work?
  
  Kees
  
  ___
  Beginners mailing list
  Beginners@haskell.org (mailto:Beginners@haskell.org)
  http://www.haskell.org/mailman/listinfo/beginners
 






--

Message: 2
Date: Wed, 6 Jun 2012 08:52:44 +0200
From: Rico Moorman rico.moor...@gmail.com
Subject: Re: [Haskell-beginners] wrapping text in a multiline string
To: Arlen Cuss a...@unnali.com
Cc: beginners@haskell.org
Message-ID:
cajrzcx1qybl8pdqck1-bkf7by8ovewzkaxxfheghosbwrch...@mail.gmail.com
Content-Type: text/plain; charset=windows-1252

Thank you very much for this suggestion. I just tried the character class
you mentioned and it works.

The stackoverflow post you mentioned was a nice read and I surely agree
that regular expressions are normally not the way to go for most HTML
munging needs. But luckily the generated HTML from pandoc is very specific
and the table tag I wanted to match (for line-numbered code listings)
does not contain any further tables so I thought it should be safe to
approach it like this.

The resulting code is now:

-- Wraps numbered code listings within the page body with a div
-- in order to be able to apply some more specific styling.
wrapNumberedCodelistings (Page meta body) =
Page meta newBody
where
newBody = regexReplace
table\\s+class=\sourceCode[^]+[\\s\\S]*?/table wrap body
wrap x = div class=\sourceCodeWrap\ ++ x ++ /div

-- Replaces the whole match for the given regex using the given function
regexReplace :: String - (String - String) - String - String
regexReplace regex replace text = go text
where
go text = case text =~~ regex of
Just (before, match, after) -
before ++ replace match ++ go after
_ - text

Don't know though if it could be cleaned up further or even if this is by
any means good style (being still fairly new to haskell).

Furthermore I would still be very interested in the right approach to
manipulating the HTML structure as a whole and I too hope that another
Haskeller could name a more suitable solution for manipulating HTML.
Or even how to pass the 's' modifier to Text.Regex.PCRE.

Best regards,

rico

On Wed, Jun 6, 2012 at 7:11 AM, Arlen Cuss a...@unnali.com wrote:

 I'd be more inclined to look at a solution involving manipulating the HTML
 structure, rather than trying a regexp-based approach, which will probably
 end up disappointing. (See this: http://stackoverflow.com/a/1732454/499609
 )

 I hope another Haskeller can speak to a library that would be good for
 

Beginners Digest, Vol 48, Issue 8

2012-06-06 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  wrapping text in a multiline string (Rico Moorman)


--

Message: 1
Date: Wed, 6 Jun 2012 10:39:28 +0200
From: Rico Moorman rico.moor...@gmail.com
Subject: Re: [Haskell-beginners] wrapping text in a multiline string
To: Arlen Cuss a...@unnali.com
Cc: beginners@haskell.org
Message-ID:
CAJrzcX2-CSesYFfqFOGUSmDebYt3frrmJbT8_sy_792oMq=P=w...@mail.gmail.com
Content-Type: text/plain; charset=windows-1252

Thank you again!

Looking at the docs it seems that this could do the trick. A pity that
you cannot install the package.

Now I am wondering how I would integrate this in the replacement
function or how to rewrite it properly.

Looking at the type signature of =~~ (with my limited knowledge) it
seems that I would have to use RegexMaker adding up the CompOptions
needed?

(=~~)?:: (RegexMaker?Regex?CompOption?ExecOption?source,?RegexContext
Regex?source1 target,?Monad?m) = source1 - source - m target


On Wed, Jun 6, 2012 at 9:46 AM, Arlen Cuss a...@unnali.com wrote:

 Exploring the documentation for Text.Regex.PCRE, I've found CompOption:

 http://hackage.haskell.org/packages/archive/regex-pcre/0.94.4/doc/html/Text-Regex-PCRE-Wrap.html#t:CompOption

 The constants are listed below; the one you want is probably compDotAll, to 
 make . match newlines as well. I'm not 100% sure if this is the module you 
 want, though, and I can't seem to get regex-pcre installed, so I can't test. 
 Apologies!


 On Wednesday, 6 June 2012 at 4:52 PM, Rico Moorman wrote:

  Thank you very much for this suggestion. I just tried the character class 
  you mentioned and it works.
 
  The stackoverflow post you mentioned was a nice read and I surely agree 
  that regular expressions are normally not the way to go for most HTML 
  munging needs. But luckily the generated HTML from pandoc is very specific 
  and the table tag I wanted to match (for line-numbered code listings) 
  does not contain any further tables so I thought it should be safe to 
  approach it like this.
 
  The resulting code is now:
 
  -- Wraps numbered code listings within the page body with a div
  -- in order to be able to apply some more specific styling.
  wrapNumberedCodelistings (Page meta body) =
  Page meta newBody
  where
  newBody = regexReplace 
  table\\s+class=\sourceCode[^]+[\\s\\S]*?/table wrap body
  wrap x = div class=\sourceCodeWrap\ ++ x ++ /div
 
  -- Replaces the whole match for the given regex using the given function
  regexReplace :: String - (String - String) - String - String
  regexReplace regex replace text = go text
  where
  go text = case text =~~ regex of
  Just (before, match, after) -
  before ++ replace match ++ go after
  _ - text
 
 
  Don't know though if it could be cleaned up further or even if this is by 
  any means good style (being still fairly new to haskell).
 
  Furthermore I would still be very interested in the right approach to 
  manipulating the HTML structure as a whole and I too hope that another 
  Haskeller could name a more suitable solution for manipulating HTML.
  Or even how to pass the 's' modifier to Text.Regex.PCRE.
 
  Best regards,
 
  rico
 
  On Wed, Jun 6, 2012 at 7:11 AM, Arlen Cuss a...@unnali.com 
  (mailto:a...@unnali.com) wrote:
   I'd be more inclined to look at a solution involving manipulating the 
   HTML structure, rather than trying a regexp-based approach, which will 
   probably end up disappointing. (See this: 
   http://stackoverflow.com/a/1732454/499609)
  
   I hope another Haskeller can speak to a library that would be good for 
   this kind of purpose.
  
   To suit what you're doing now, though; if you change .*? to [\s\S]*?, it 
   should work on multiline strings. If you can work out how to pass the 's' 
   modifier to Text.Regexp.PCRE, that should also do it.
  
   ?Arlen
  
  
   On Wednesday, 6 June 2012 at 3:05 PM, Rico Moorman wrote:
  
Hello,
   
I have a given piece of multiline HTML (which is generated using pandoc 
btw.) and I am trying to wrap certain elements (tags with a given 
class) with a div.
   
I already took a look at the Text.Regex.PCRE module which seemed a 
reasonable choice because I am already familiar with similar regex 
implementations in other languages.
   
I came up with the following function which takes a regex and replaces 
all matches within the given string using the provided function (which 
I would use to wrap the element)
  

Beginners Digest, Vol 48, Issue 9

2012-06-06 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  flatten comma operator (Brent Yorgey)
   2. Re:  flatten comma operator (Arlen Cuss)
   3. Re:  wrapping text in a multiline string (Arlen Cuss)
   4. Re:  wxHaskell path (Henry Lockyer)
   5. Re:  wxHaskell install errors (Heinrich Apfelmus)
   6. Re:  histogram over large data (Ben Gamari)


--

Message: 1
Date: Wed, 6 Jun 2012 06:58:57 -0400
From: Brent Yorgey byor...@seas.upenn.edu
Subject: Re: [Haskell-beginners] flatten comma operator
To: beginners@haskell.org
Message-ID: 20120606105857.ga17...@seas.upenn.edu
Content-Type: text/plain; charset=us-ascii

On Wed, Jun 06, 2012 at 09:46:58AM +0200, Kees Bleijenberg wrote:
 This is indeed the code I was talking about.
 I did not understand how I could create (1,2,3) with the comma operator
 (,)((,) 1 2) 3 = ((1,2),3) and not (1,2,3). That's why I thought I needed a
 kind of join operation to 'flatten' this.

It's not possible to create a triple using only the (,) operator --
there's no way to do the join/flatten operation you have in mind,
because there's no valid type it could be assigned (unless you make it
specific to three-tuples, but I'm guessing you have something more
general in mind).

 Indeed (,,) 1 2 3 is (1,2,3). But I do not understand what is happening. Is
 (,,) predefined? Probably not.

Yes, it is!

-Brent



--

Message: 2
Date: Wed, 6 Jun 2012 21:06:04 +1000
From: Arlen Cuss a...@unnali.com
Subject: Re: [Haskell-beginners] flatten comma operator
To: Kees Bleijenberg k.bleijenb...@inter.nl.net
Cc: beginners@haskell.org
Message-ID: c5d52883eeb84f3da1d3d38db8a9c...@unnali.com
Content-Type: text/plain; charset=utf-8

On Wednesday, 6 June 2012 at 5:46 PM, Kees Bleijenberg wrote:
 This is indeed the code I was talking about.
 I did not understand how I could create (1,2,3) with the comma operator
 (,)((,) 1 2) 3 = ((1,2),3) and not (1,2,3). That's why I thought I needed a
 kind of join operation to 'flatten' this.

As Brent pointed out, you can't without making it very specific. Each length of 
tuple with its combination of types is a unique type itself; compare to a list, 
where [a] is the type for a list of any length (including zero) containing 
elements of type a. A list is trivial to append to, whereas tuples are not 
designed for extension in this manner, per se.
 Indeed (,,) 1 2 3 is (1,2,3). But I do not understand what is happening. Is
 (,,) predefined? Probably not.

And as Brent pointed out also, it is. :)  By the way, so is 
(,,,)!
  I suspect GHC allows any number.  The Haskell Report section 6.1.4 [1] says 
implementations must support up to at least 15. 

Cheers,

Arlen

[1] http://www.haskell.org/onlinereport/basic.html 
 
 
 -Oorspronkelijk bericht-
 Van: Arlen Cuss [mailto:a...@unnali.com] 
 Verzonden: woensdag 6 juni 2012 8:43
 Aan: Kees Bleijenberg
 CC: beginners@haskell.org (mailto:beginners@haskell.org)
 Onderwerp: Re: [Haskell-beginners] flatten comma operator
 
 By the way, is the excerpt from RWH involving liftA2 the chapter on using
 Parsec? If so, this may be the code snippet you refer to:
 
 -- file: ch16/FormApp.hs a_pair :: CharParser () (String, Maybe String)
 a_pair = liftA2 (,) (many1 a_char) (optionMaybe (char '=' * many a_char))
 
 In this case, liftA2 is promoting the (,) operation to work with the two
 operations in the CharParser applicative functor.
 
 (,) is of type a - b - (a,b), so without lifting, we'd end up with
 something like (CharParser () String, CharParser () Maybe String) (just a
 guess here).
 
 liftA2 produces a new applicative functor action which computes each of
 (many1 a_char) and (optionMaybe (char '=' * many a_char)), then gives the
 pure results to (,). 
 
 
 On Wednesday, 6 June 2012 at 4:36 PM, Arlen Cuss wrote:
 
  If (,) is a function that takes two elements and returns the 2-tuple, 
  have you considered something like (,,)? :)
  
  
  
  On Wednesday, 6 June 2012 at 4:33 PM, Kees Bleijenberg wrote:
  
   In 'Real World Haskell' I found code like LiftA2 (,) 
   Looks odd. But after some experimenting in winghci I found that (,) 1 2
  
 
 
 is valid code and is equal to (1,2).
   Now I wonder how to create (1,2,3). I think you need a join or a flatten
  
 
 
 function or ...? 

Beginners Digest, Vol 48, Issue 10

2012-06-06 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  wxHaskell install errors (carlos gomez)
   2. Re:  wxHaskell install errors (Gregory Guthrie)
   3. Re:  wxHaskell install errors (Gregory Guthrie)
   4. Re:  graphics.gloss errors (Chadda? Fouch?)
   5. Re:  wrapping text in a multiline string (Chadda? Fouch?)
   6. Re:  wxHaskell install errors (carlos gomez)
   7. Re:  wrapping text in a multiline string (Rico Moorman)


--

Message: 1
Date: Wed, 6 Jun 2012 12:38:37 -0400
From: carlos gomez carliro...@gmail.com
Subject: Re: [Haskell-beginners] wxHaskell install errors
To: Gregory Guthrie guth...@mum.edu
Cc: beginners@haskell.org beginners@haskell.org
Message-ID:
cahg7derurgkleja8yhdgb73nymrpt8c7nvft2u5+brbkeea...@mail.gmail.com
Content-Type: text/plain; charset=windows-1252

Is your wx-config working ?
You can try:  *wx-config ?help*

If not, try with another, you can use these ones:

-   download from https://sites.google.com/site/wxconfig/sourcecode
and compile with g++ wx-config.cpp -o wx-config.exe
-   or download directly the .exe from
http://sourceforge.net/projects/wxhaskell/files/wx-config-win/

Regards,
Carlos Gomez

On 5 June 2012 16:23, Gregory Guthrie guth...@mum.edu wrote:

 I had all of the wxHaskell programs installed and working fine, but now
 with an update to Haskell Platform and thus also ghci, I need to upgrade
 all of them (the previously working programs fail) requiring an update for
 the underlying wxWidgets from 2.8 to 2.9 versions.

 I downloaded and built wxWidgets 2.9, since the current wxHaskell
 libraries require it (I couldn't find any existing binaries online).
 The compile seemed to be successful, but when I then try to use it from
 the wxHaskell programs I get an error that I don't know how to fix:

 C: cabal install wx
 Resolving dependencies...
 [1 of 1] Compiling Main (
 C:\Users\guthrie\AppData\Local\Temp\wxc-0.
 90.0.3-7324\wxc-0.90.0.3\Setup.hs,
 C:\Users\guthrie\AppData\Local\Temp\wxc-0.90.
 0.3-7324\wxc-0.90.0.3\dist\setup\Main.o ) Linking
 C:\Users\guthrie\AppData\Local\Temp\wxc-0.90.0.3-7324\wxc-0.90.0.3\dist\
 setup\setup.exe ...
 Configuring wxc-0.90.0.3...
 Configuring wxc to build against wxWidgets 2.9

 setup.exe: Missing dependencies on foreign libraries:
 * Missing C libraries: wxmsw29ud_all, wxtiffd, wxjpegd, wxpngd,
 wxzlibd,wxregexud, wxexpatd, wxregexud This problem can usually be solved
 by installing the system packages that provide these libraries (you may
 need the -dev versions). If the libraries are already installed but in a
 non-standard location then you can use the flags --extra-include-dirs= and
 --extra-lib-dirs= to specify where they are.
 cabal: Error: some packages failed to install:
 wx-0.90.0.1 depends on wxc-0.90.0.3 which failed to install.
 wxc-0.90.0.3 failed during the configure step. The exception was:
 ExitFailure 1
 wxcore-0.90.0.1 depends on wxc-0.90.0.3 which failed to install.


 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners

-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120606/5f3a5106/attachment-0001.htm

--

Message: 2
Date: Wed, 6 Jun 2012 11:42:58 -0500
From: Gregory Guthrie guth...@mum.edu
Subject: Re: [Haskell-beginners] wxHaskell install errors
To: carlos gomez carliro...@gmail.com
Cc: beginners@haskell.org beginners@haskell.org
Message-ID:
08ef9da445c4b5439c4733e1f35705ba01a2767cb...@mail.cs.mum.edu
Content-Type: text/plain; charset=iso-8859-1

Thanks, yes - it seems good, it responds with a help menu message.

 Subject: Re: [Haskell-beginners] wxHaskell install errors
 
 Is your wx-config working ?
 You can try:??wx-config -help?

 If not, try with another, you can use these ones:

 - ? download from https://sites.google.com/site/wxconfig/sourcecode
? ? and compile with?g++ wx-config.cpp -o wx-config.exe
- ? or download directly the .exe from 
??http://sourceforge.net/projects/wxhaskell/files/wx-config-win/
? ??
Regards,
Carlos Gomez



--

Message: 3
Date: Wed, 6 Jun 2012 11:52:03 -0500
From: Gregory Guthrie guth...@mum.edu
Subject: Re: [Haskell-beginners] wxHaskell install errors
To: beginners@haskell.org beginners@haskell.org
Message-ID:
08ef9da445c4b5439c4733e1f35705ba01a2767cb...@mail.cs.mum.edu

Beginners Digest, Vol 48, Issue 11

2012-06-06 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  wxHaskell install errors (Gregory Guthrie)
   2. Re:  flatten comma operator (Brandon Allbery)
   3. Re:  wxHaskell path (Miguel Negrao)
   4. Re:  wxHaskell path (Henry Lockyer)
   5. Re:  wxHaskell install errors (carlos gomez)


--

Message: 1
Date: Wed, 6 Jun 2012 15:15:20 -0500
From: Gregory Guthrie guth...@mum.edu
Subject: Re: [Haskell-beginners] wxHaskell install errors
To: carlos gomez carliro...@gmail.com
Cc: beginners@haskell.org beginners@haskell.org
Message-ID:
08ef9da445c4b5439c4733e1f35705ba01a2767cb...@mail.cs.mum.edu
Content-Type: text/plain; charset=us-ascii

 First, you should make sure for yourself that wxWidgets 2.9 is well 
 installed, for that you can try to build the wxwidgets' examples

 cd c:\wx\samples\minimal
 mingw32-make -f makefile.gcc BUILD=debug 

Thanks, good test, it fails.

 /e/plang/libraries/wxWidgets2.9/samples/minimal 
 $ mingw32-make -f makefile.gcc BUILD=debug
 if not exist gcc_mswuddll mkdir gcc_mswuddll
 windres --use-temp-file -i../../samples/sample.rc 
-ogcc_mswuddll\minimal_sample_rc.o--define __WXMSW__   --define 
_UNICODE  -- include-dir .\..\..\lib\gc
 c_dll\mswud --include-dir ./../../include  --include-dir . --define 
WXUSINGDLL --include-dir ./../../samples --define NOPCH
 g++ -c -o gcc_mswuddll\minimal_minimal.o -g -O0 -mthreads  -DHAVE_W32API_H 
-D__WXMSW__   -D_UNICODE  -I.\..\..\lib\gcc_dll\mswud -I.\..\..\include  -W 
-Wall
  -I. -DWXUSINGDLL -I.\..\..\samples -DNOPCH   -Wno-ctor-dtor-privacy   
-MTgcc_mswuddll\minimal_minimal.o  -MFgcc_mswuddll\minimal_minimal.o.d -MD 
-MP minimal.cpp

 In file included from .\..\..\include/wx/defs.h:28:0,
 from .\..\..\include/wx/wxprec.h:13,
 from minimal.cpp:21:
 .\..\..\include/wx/platform.h:181:22: fatal error: wx/setup.h: No such 
file or directory
 compilation terminated.
 mingw32-make: *** [gcc_mswuddll\minimal_minimal.o] Error 1

(I did have to start a mingw shell to do this, it won't run from a cmd line.)
Not sure what to make of it...

I still wish I could just get a binary to install like was available from 
wxPack for 2.8!  :-)


 Then, I can think that it is just a problem of configuring and installing 
 wxhaskell.

 For the paths you have to set, probably the wxc is not installed on your pc 
 yet, and probably that's why you couldn't find. 
 But you should follow the way setting those paths and put the right versions 
 of the libraries you are installing.

Yes, probably wxc is not installed, but that is the problem I am stuck at I 
think.



--

Message: 2
Date: Wed, 6 Jun 2012 17:17:27 -0400
From: Brandon Allbery allber...@gmail.com
Subject: Re: [Haskell-beginners] flatten comma operator
To: Arlen Cuss a...@unnali.com
Cc: beginners@haskell.org
Message-ID:
CAKFCL4U=g1_bSPPk=0qjw+g7oauwoc2nokor8bavokuagko...@mail.gmail.com
Content-Type: text/plain; charset=utf-8

On Wed, Jun 6, 2012 at 7:06 AM, Arlen Cuss a...@unnali.com wrote:

 And as Brent pointed out also, it is. :)  By the way, so is
 (,,,)!
  I suspect GHC allows any number.  The


Maybe not any number; more than 127 elements in a tuple used to cause core
dumps

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120606/eb1313f2/attachment-0001.htm

--

Message: 3
Date: Wed, 6 Jun 2012 22:18:49 +0100
From: Miguel Negrao miguel.negrao-li...@friendlyvirus.org
Subject: Re: [Haskell-beginners] wxHaskell path
To: beginners@haskell.org
Message-ID: e5654eb9-0f84-46ac-8f59-99e795c19...@friendlyvirus.org
Content-Type: text/plain; charset=windows-1252

Hi Henry,

A 06/06/2012, ?s 12:31, Henry Lockyer escreveu:

 Thanks a lot Miguel.   I recently discovered your posts about 'reactive 
 banana' and wxHaskell and started looking through them.
 
 Unfortunately I am a c/c++ compilation/make/etc. and general unix newbie, or 
 oldbie in my case, (amongst many other areas of deep ignorance 

Beginners Digest, Vol 48, Issue 12

2012-06-07 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  wxHaskell install errors (Henry Lockyer)
   2. Re:  wxHaskell install errors (Gregory Guthrie)
   3. Re:  wxHaskell install errors (Gregory Guthrie)
   4. Re:  wxHaskell install errors (Gregory Guthrie)
   5. Re:  wxHaskell install errors (carlos gomez)
   6. Re:  wxHaskell install errors (Henry Lockyer)


--

Message: 1
Date: Thu, 7 Jun 2012 01:55:25 +0100
From: Henry Lockyer henry.lock...@ntlworld.com
Subject: Re: [Haskell-beginners] wxHaskell install errors
To: Gregory Guthrie guth...@mum.edu
Cc: beginners@haskell.org
Message-ID: 576a8abf-8df6-4bb0-a876-140155821...@ntlworld.com
Content-Type: text/plain; charset=us-ascii

Hi Gregory, just been looking at your thread here 
(We seem to be having somewhat parallel problems - I am struggling with 
installing wxHAskell on mac osx).

I was wondering, if you give the command wx-config --release
What do you get ?
If it says 2.8 (which is what I get) then presumably your 'path' is still 
pointing to the earlier version. And this would fit with Heinrich Apfelmus's
comments ?

I am struggling to make sense of path settings, and I raised some questions in 
another thread/s.

In the wxHaskell installation instructions for wxWidgets 2.8  I saw this:
We assume in this guide that the variable $wxwin points to your wxWidgets 
installation directory, for example: ~/dev/wxGTK-2.8.10.
It is not in a windows specific part of the instructions, though I wonder (from 
the name) if it is just relevant for windows (though 'win' could also
denote 'Widgets INstallation' perhaps).

Do you recognise $wxwin (and what is it set to in your case?).
I wonder if this may be implicated in the path settings for 2.9 too.

I was also very interested by your If the libraries
are already installed but in a non-standard location then you can use the
flags --extra-include-dirs= and --extra-lib-dirs= to specify where they 
are.

I have not got to the cabal step yet (still trying to reach some confidence I 
have widgets installed and configured correctly!) but it seems this
may be the (at least an) answer to the path aspect if all else fails with 
trying to get an auto default path working.

Cheers/ Henry


On 6 Jun 2012, at 21:15, Gregory Guthrie wrote:

 First, you should make sure for yourself that wxWidgets 2.9 is well 
 installed, for that you can try to build the wxwidgets' examples
 
 cd c:\wx\samples\minimal
 mingw32-make -f makefile.gcc BUILD=debug 
 
 Thanks, good test, it fails.
 
 /e/plang/libraries/wxWidgets2.9/samples/minimal 
 $ mingw32-make -f makefile.gcc BUILD=debug
 if not exist gcc_mswuddll mkdir gcc_mswuddll
 windres --use-temp-file -i../../samples/sample.rc 
 -ogcc_mswuddll\minimal_sample_rc.o--define __WXMSW__   --define 
 _UNICODE  -- include-dir .\..\..\lib\gc
 c_dll\mswud --include-dir ./../../include  --include-dir . --define 
 WXUSINGDLL --include-dir ./../../samples --define NOPCH
 g++ -c -o gcc_mswuddll\minimal_minimal.o -g -O0 -mthreads  
 -DHAVE_W32API_H -D__WXMSW__   -D_UNICODE  -I.\..\..\lib\gcc_dll\mswud 
 -I.\..\..\include  -W -Wall
  -I. -DWXUSINGDLL -I.\..\..\samples -DNOPCH   -Wno-ctor-dtor-privacy   
 -MTgcc_mswuddll\minimal_minimal.o  -MFgcc_mswuddll\minimal_minimal.o.d 
 -MD -MP minimal.cpp
 
 In file included from .\..\..\include/wx/defs.h:28:0,
 from .\..\..\include/wx/wxprec.h:13,
 from minimal.cpp:21:
 .\..\..\include/wx/platform.h:181:22: fatal error: wx/setup.h: No such 
 file or directory
 compilation terminated.
 mingw32-make: *** [gcc_mswuddll\minimal_minimal.o] Error 1
 
 (I did have to start a mingw shell to do this, it won't run from a cmd line.)
 Not sure what to make of it...
 
 I still wish I could just get a binary to install like was available from 
 wxPack for 2.8!  :-)
 
 
 Then, I can think that it is just a problem of configuring and installing 
 wxhaskell.
 
 For the paths you have to set, probably the wxc is not installed on your pc 
 yet, and probably that's why you couldn't find. 
 But you should follow the way setting those paths and put the right versions 
 of the libraries you are installing.
 
 Yes, probably wxc is not installed, but that is the problem I am stuck at I 
 think.
 
 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners

-- next part 

Beginners Digest, Vol 48, Issue 13

2012-06-07 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  wxHaskell path (Henry Lockyer)


--

Message: 1
Date: Thu, 7 Jun 2012 10:56:30 +0100
From: Henry Lockyer henry.lock...@ntlworld.com
Subject: Re: [Haskell-beginners] wxHaskell path
To: beginners@haskell.org
Message-ID: 4c4be76f-6e35-4cf3-9c61-7944697d7...@ntlworld.com
Content-Type: text/plain; charset=us-ascii

Anyone know if/how  $wxwin also needs to be set on macosx 
for wxHaskell 0.9 /wxWidgets 2.8 ?  
and/or wxHAskell 0.13 / wxWidgets 2.9 ?





--

___
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 48, Issue 13
*


Beginners Digest, Vol 48, Issue 14

2012-06-07 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  Strange difference in behaviour between ghc and  ghci
  (Matthew Moppett)
   2. Re:  Strange difference in behaviour between ghc and ghci
  (Arlen Cuss)
   3. Re:  flatten comma operator (Arlen Cuss)
   4. Re:  Strange difference in behaviour between ghc and ghci
  (Andres L?h)
   5. Re:  Strange difference in behaviour between ghc  and ghci
  (Henry Lockyer)
   6. Re:  Strange difference in behaviour between ghc  and ghci
  (Henry Lockyer)
   7. Re:  Strange difference in behaviour between ghc and ghci
  (Matthew Moppett)


--

Message: 1
Date: Thu, 7 Jun 2012 21:22:23 +1000
From: Matthew Moppett matthewmopp...@gmail.com
Subject: [Haskell-beginners] Strange difference in behaviour between
ghc and ghci
To: beginners@haskell.org
Message-ID:
CAMLEjZAi7waUto4TaqegwJ1-4eBCT=ifcvjaylatpjuxkcp...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

I have a very simple Haskell file (HelloWorld.hs) that reads like this:

main = do
putStr What's your name? 
n - getLine
putStrLn $ Pleased to meet you,  ++ n

When I load it into ghci, I get the following result, as expected:

[1 of 1] Compiling Main ( HelloWorld.hs, interpreted )
Ok, modules loaded: Main.
*Main main
What's your name? Matt
Pleased to meet you, Matt
*Main

However, when I compile the same file using ghc and run it in a terminal, I
get a very different result:

matt@matt-Lenovo-G575:~/Haskell$ ghc HelloWorld.hs
[1 of 1] Compiling Main ( HelloWorld.hs, HelloWorld.o )
Linking HelloWorld ...
matt@matt-Lenovo-G575:~/Haskell$ ./HelloWorld
Matt
What's your name? Pleased to meet you, Matt
matt@matt-Lenovo-G575:~/Haskell$


-- in other words, the getLine action is being run before the putStr
action, for some strange reason.

Is this a bug? Can anyone enlighten me as to what might be going on?

Regards,

Matt.
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120607/90f03058/attachment-0001.htm

--

Message: 2
Date: Thu, 7 Jun 2012 21:28:53 +1000
From: Arlen Cuss a...@unnali.com
Subject: Re: [Haskell-beginners] Strange difference in behaviour
between ghc and ghci
To: Matthew Moppett matthewmopp...@gmail.com
Cc: beginners@haskell.org
Message-ID: 525ca83d7d7c47888342df367da02...@unnali.com
Content-Type: text/plain; charset=utf-8

Hello! 

See this similar mailing list question from 2006:

http://www.haskell.org/pipermail/haskell/2006-September/018430.html

The short answer is that GHCi buffers differently, so you need to be more 
explicit about flushing.

HTH,

Arlen 


On Thursday, 7 June 2012 at 9:22 PM, Matthew Moppett wrote:

 I have a very simple Haskell file (HelloWorld.hs) that reads like this:
 
 main = do
 putStr What's your name? 
 n - getLine
 putStrLn $ Pleased to meet you,  ++ n
 
 
 When I load it into ghci, I get the following result, as expected:
 
 [1 of 1] Compiling Main ( HelloWorld.hs, interpreted )
 Ok, modules loaded: Main.
 *Main main
 What's your name? Matt
 Pleased to meet you, Matt
 *Main 
 
 
 However, when I compile the same file using ghc and run it in a terminal, I 
 get a very different result: 
 
 matt@matt-Lenovo-G575:~/Haskell$ ghc HelloWorld.hs
 [1 of 1] Compiling Main ( HelloWorld.hs, HelloWorld.o )
 Linking HelloWorld ...
 matt@matt-Lenovo-G575:~/Haskell$ ./HelloWorld
 Matt
 What's your name? Pleased to meet you, Matt
 matt@matt-Lenovo-G575:~/Haskell$ 
 
 
 
 -- in other words, the getLine action is being run before the putStr action, 
 for some strange reason. 
 
 Is this a bug? Can anyone enlighten me as to what might be going on?
 
 Regards,
 
 Matt. 
 ___
 Beginners mailing list
 Beginners@haskell.org (mailto:Beginners@haskell.org)
 http://www.haskell.org/mailman/listinfo/beginners






--

Message: 3
Date: Thu, 7 Jun 2012 21:30:32 +1000
From: Arlen Cuss a...@unnali.com
Subject: Re: [Haskell-beginners] flatten comma operator
To: Brandon Allbery allber...@gmail.com
Cc: beginners@haskell.org
Message-ID: e6227490970f4be6a30ba0462f72c...@unnali.com
Content-Type: text/plain; charset=utf-8

Hmm. I've tested over 6,432 to work, but I'm not sure this has any point any 
more ? ;-)



On Thursday, 7 June 2012 at 7:17 AM, Brandon Allbery wrote:

 On Wed, Jun 6, 2012 at 7:06 AM, Arlen Cuss 

Beginners Digest, Vol 48, Issue 15

2012-06-07 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  wrapping text in a multiline string (Rico Moorman)
   2. Re:  wxHaskell path (Heinrich Apfelmus)
   3. Re:  reactiva-banana : how to implement a certain type of
  throttling (Heinrich Apfelmus)
   4. Re:  wxHaskell path (Henry Lockyer)
   5. Re:  wxHaskell path (Henry Lockyer)
   6. Re:  wrapping text in a multiline string (Chadda? Fouch?)
   7. Re:  wxHaskell install errors (Gregory Guthrie)


--

Message: 1
Date: Thu, 7 Jun 2012 14:44:11 +0200
From: Rico Moorman rico.moor...@gmail.com
Subject: Re: [Haskell-beginners] wrapping text in a multiline string
To: Chadda? Fouch? chaddai.fou...@gmail.com
Cc: beginners@haskell.org
Message-ID:
CAJrzcX1w0JQ4AO95J=urfkai6ko00hpnegjgu_lkdf_mkmw...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

 What's non-obvious and trip a lot of people when they try to use
 regexes in Haskell is that most regex libraries use the same
 interface, which is specified in the regex-base and consists of
 several typeclasses that offers a very high degree of flexibility.
 =~and =~~ are only the simplified front-ends to this and are pretty
 inadequate for advanced usages (for instance compile and use multiple
 time the same regex, you should really avoid =~ in this case, or
 additional regex compilation options). To see the basic interface,
 look at Text.Regex.Base.RegexLike :
 http://hackage.haskell.org/packages/archive/regex-base/latest/doc/html/Text-Regex-Base-RegexLike.html
 .
 In particular, what you want to do should be done with makeRegexOpts
 and match (or matchM), note that the available compilation and
 execution options can vary depending on the regex library you use and
 for regex-pcre, they're documented there :
 http://hackage.haskell.org/packages/archive/regex-pcre/latest/doc/html/Text-Regex-PCRE-Wrap.html#g:4

 --
 Jeda?

By the way, do you know other good resources on Regular expressions in
Haskell and especially the multiple backends (tdfa, posix and pcre
e.g.) in combination with the basic interface and how to use this all
together? Some example code would be really useful.

Furthermore the following page states that the Text.Regex.Base stuff
is being exported again by the newer/other regex modules.

http://hackage.haskell.org/packages/archive/regex-base/0.93.2/doc/html/Text-Regex-Base-Context.html

Does this mean I should use the specific regex modules directly or
should I import the base and then specific functionality from the
engine modules?

Thank you very much in advance,

Best regards,

Rico



--

Message: 2
Date: Thu, 07 Jun 2012 14:44:35 +0200
From: Heinrich Apfelmus apfel...@quantentunnel.de
Subject: Re: [Haskell-beginners] wxHaskell path
To: beginners@haskell.org
Message-ID: jqq7nj$2if$1...@dough.gmane.org
Content-Type: text/plain; charset=UTF-8; format=flowed

Henry Lockyer wrote:
 Anyone know if/how  $wxwin also needs to be set on macosx 
 for wxHaskell 0.9 /wxWidgets 2.8 ?  
 and/or wxHAskell 0.13 / wxWidgets 2.9 ?

I don't think it's needed. Installation instruction found on the 
internet are not always accurate.


Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com




--

Message: 3
Date: Thu, 07 Jun 2012 15:52:07 +0200
From: Heinrich Apfelmus apfel...@quantentunnel.de
Subject: Re: [Haskell-beginners] reactiva-banana : how to implement a
certain type of throttling
To: beginners@haskell.org
Message-ID: jqqbm7$5tv$1...@dough.gmane.org
Content-Type: text/plain; charset=UTF-8; format=flowed

Miguel Negrao wrote:
 A 04/06/2012, ?s 16:11, Heinrich Apfelmus escreveu:
 
 Miguel, could you repost this question on Stackoverflow, so I can answer it 
 there?

 I?ve reposted the question here: [..]

Thanks!

 Ok, looking at Wave.hs I can see what I need to do to be able to 
 delay an event by a certain amount of seconds. The scheduleQueue
 function there doesn?t exactly do what I need it to do, because it
 schedules relative to the last scheduled event. Essentially I would
 need to alter it such that the scheduling is done in absolute terms,
 so If I ask something to happen 5 seconds from now it should really
 happen 5 seconds from now instead of 5 seconds from the last event in
 queue. One way to do it would be to keep the scheduled times in UTC
 or some other time format and every time an event comes into the
 queue stop the timer, sort the event queue by the absolute times,
 check how long is 

Beginners Digest, Vol 48, Issue 16

2012-06-09 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  Scoping within arrow notation (using HXT)? (Michael Alan Dorman)
   2. Re:  Scoping within arrow notation (using HXT)?
  (Ertugrul S?ylemez)


--

Message: 1
Date: Fri, 08 Jun 2012 11:48:23 -0400
From: Michael Alan Dorman mdor...@ironicdesign.com
Subject: [Haskell-beginners] Scoping within arrow notation (using
HXT)?
To: beginners@haskell.org
Message-ID: 87vcj1vm7s@ironicdesign.com
Content-Type: text/plain

Hey, Haskellers,

I'm trying to use state threaded through an arrow in some HXT code to
avoid passing explicit parameters through several layers of functions,
but I think I'm not understanding quite what the arrow notation is
doing, because when I try to use a value I'm extracting from the state,
I'm getting a scope error.

I had many ways I was prepared for the code to be wrong, but that one
has me baffled.  Any suggestions?

Mike.

{-# LANGUAGE Arrows, NoMonomorphismRestriction #-}
module HXTTest () where
import Text.XML.HXT.Core

data Info = Info {
  value :: String
} deriving (Show)

info = Info { value = foo }
html = htmlhead/headbodydiv class='foo'llama/div/body;

-- print (runSLA (getState  arr value) info html)

-- Div class is static, no reference to state
findFoo =
  proc content - do
(deep (isElem 
   hasName div 
   hasAttrValue class (== foo))) - content

-- print (runSLA (hread  findFoo) info html)

-- Extract class from state, but don't use it
findFoo' =
  proc content - do
divName - (getState  arr value) - content
content - (deep (isElem 
  hasName div 
  hasAttrValue class (== foo)))

-- print (runSLA (hread  findFoo') info html)

-- Extract class from state, try to use it: Not in scope: `divName'
-- findFoo'' =
--   proc content - do
-- divName - (getState  arr value) - content
-- content - (deep (isElem 
--   hasName div 
--   hasAttrValue class (== divName)))




--

Message: 2
Date: Fri, 8 Jun 2012 18:20:13 +0200
From: Ertugrul S?ylemez e...@ertes.de
Subject: Re: [Haskell-beginners] Scoping within arrow notation (using
HXT)?
To: beginners@haskell.org
Message-ID: 20120608182013.5ffd1...@angst.streitmacht.eu
Content-Type: text/plain; charset=us-ascii

Hello there,

the structure of an arrow computation cannot depend on inputs.  All
arrow variables (to the left of '-' or '-') are inputs to following
computations.  For instance:

proc x1 - do
x2 - c1 - x1
x3 - c2 - x2
returnA - f x2 x3

The variables x1, x2 and x3 are arrow variables and are out of scope
to the left of '-', because if they were in scope, the structure of the
computation could depend on arrow variables, and you would in fact have
a monad instead of an arrow.

Note also that 'proc x - c - x' is the same as 'c', and 'do' notation
is an extension to 'proc' notation.

You may be interested in my (unfinished) arrow tutorial:

http://ertes.de/new/tutorials/arrows.html


Greets,
Ertugrul


Michael Alan Dorman mdor...@ironicdesign.com wrote:

 I'm trying to use state threaded through an arrow in some HXT code to
 avoid passing explicit parameters through several layers of functions,
 but I think I'm not understanding quite what the arrow notation is
 doing, because when I try to use a value I'm extracting from the
 state, I'm getting a scope error.

-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/
-- next part --
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 836 bytes
Desc: not available
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120608/f596dfd6/attachment-0001.pgp

--

___
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 48, Issue 16
*


Beginners Digest, Vol 48, Issue 17

2012-06-11 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  wrapping text in a multiline string (Chadda? Fouch?)
   2. Re:  wrapping text in a multiline string (Chadda? Fouch?)


--

Message: 1
Date: Sun, 10 Jun 2012 14:04:35 +0200
From: Chadda? Fouch? chaddai.fou...@gmail.com
Subject: Re: [Haskell-beginners] wrapping text in a multiline string
To: Rico Moorman rico.moor...@gmail.com
Cc: beginners beginners@haskell.org
Message-ID:
CANfjZRav-xdWgZ-4vfJG5S-21b=-vy_cgZjXCk1Jeum5mv=z=a...@mail.gmail.com
Content-Type: text/plain; charset=UTF-8

On Fri, Jun 8, 2012 at 1:33 PM, Rico Moorman rico.moor...@gmail.com wrote:
 Or you could just use matchM :

 ? ? ? ?go text = case RE.matchM regex' text of
 ? ? ? ? ? Just (before, match, after) -
 ? ? ? ? ? ? ? before ++ replace' match ++ go after
 ? ? ? ? ? _ - text

 and have match be a string, just like before (since you don't use all
 the power of MatchText anyway).

 Thank you very much for this suggestion. It works correctly. This is
 the final function (for reference):

 regexReplace :: String - (String - String) - String - String
 regexReplace pattern replace text = go text
 ? ?where
 ? ? ? ?regex = RE.makeRegexOpts compOpts RE.defaultExecOpt pattern
 ? ? ? ?compOpts = RE.compMultiline + RE.compDotAll
 ? ? ? ?go text = case RE.matchM regex text of
 ? ? ? ? ? ?Just (before, match, after) -
 ? ? ? ? ? ? ? ?before ++ replace match ++ go after
 ? ? ? ? ? ?_ - text

 It is really interesting that the result of a function can behave like
 this though. I mean that a different structure is returned based on
 the type (inferred/given) within the dependant function, e.g. [String]
 or Bool ...

This is something that's possible with typeclass in Haskell and one of
the way they differ from interfaces in the OO world. The classic
example is the Read typeclass and read :: (Read a) = String - a.

 One other thing I saw is that there can be a runtime error using the
 option compUTF8 even if the compNoUTF8Check is set too. I get:

 user error (Text.Regex.PCRE.String died: (ReturnCode (-10),Error in
 Text.Regex.PCRE.Wrap: ReturnCode (-10)))

 which is the error code for bad utf8 (PCRE_ERROR_BADUTF8) according to
 http://www.pcre.org/pcre.txt . Luckily I don't seem to need those
 options (yet). Would there be some way to catch/trace/fix those
 error somehow?

Fix I don't know since that's an internal error of the PCRE package or
library but you can catch exceptions though only in the IO monad. In
this particular case there may be an alternative since what fails is
the compilation of the regex itself and makeRegexOpts has an
alternative which handle errors : makeRegexOptsM . In this case
writing your whole replace function in the Maybe monad would probably
be a good idea :

 regexMaybeReplace :: String - (String - String) - String - Maybe String
 regexMaybeReplace pattern replace text = do
   let compOpts = RE.compMultiline + RE.compDotAll
   regex - RE.makeRegexOpts compOpts RE.defaultExecOpt pattern
   (before, match, after) - RE.matchM regex text
   return $ before ++ replace match ++ regexReplace after

 regexReplace  :: String - (String - String) - String - String
 regexReplace pattern replace text = fromMaybe text (regexMaybeReplace pattern 
 replace text)

Or something like that.

-- 
Jeda?



--

Message: 2
Date: Sun, 10 Jun 2012 14:05:45 +0200
From: Chadda? Fouch? chaddai.fou...@gmail.com
Subject: Re: [Haskell-beginners] wrapping text in a multiline string
To: Rico Moorman rico.moor...@gmail.com
Cc: beginners beginners@haskell.org
Message-ID:
CANfjZRZj2u5K=hs0gstwthbz4ychnrwguut9ix1xofj1zed...@mail.gmail.com
Content-Type: text/plain; charset=UTF-8

On Sun, Jun 10, 2012 at 2:04 PM, Chadda? Fouch?
chaddai.fou...@gmail.com wrote:

 regexMaybeReplace :: String - (String - String) - String - Maybe String
 regexMaybeReplace pattern replace text = do
 ? let compOpts = RE.compMultiline + RE.compDotAll
 ? regex - RE.makeRegexOpts compOpts RE.defaultExecOpt pattern

Oops, of course I meant :

   regex - RE.makeRegexOptsM compOpts RE.defaultExecOpt pattern



--

___
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 48, Issue 17
*


Beginners Digest, Vol 48, Issue 18

2012-06-14 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  HXT and missing or null values (Ian Knopke)
   2.  cabal trouble(s!) (Gregory Guthrie)


--

Message: 1
Date: Wed, 13 Jun 2012 16:29:32 +0100
From: Ian Knopke ian.kno...@gmail.com
Subject: [Haskell-beginners] HXT and missing or null values
To: beginners-requ...@haskell.org, beginners@haskell.org
Message-ID:
CAC+f4wkJQMYp-N==pp8c3yhinj22yy-znzb1hc-ddamh4fj...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

I have an xml file I'm trying to parse using HXT. This is the code
(for some reason the list seems to be rejecting the XML example):

data Thing = Thing {first :: String, second :: String}
  getThings = atTag thing 
  proc x - do
  first - text  atTag first - x
  second - text  atTag second - x

  returnA - Thing {first = first,second = second}

atTag tag = deep (isElem  hasName tag)

text = getChildren  getText

parseThings str = runX (readString [withValidate no] str  getThings)

The problem is that sometimes one of the tags is empty.

I'd like the code to return something like Thing
{first=val,second=} but instead the entire entry is skipped. Can
someone explain to me what I need to do to get a null or empty string
value inserted instead?

Ian



--

Message: 2
Date: Wed, 13 Jun 2012 12:23:05 -0500
From: Gregory Guthrie guth...@mum.edu
Subject: [Haskell-beginners] cabal trouble(s!)
To: beginners@haskell.org beginners@haskell.org
Message-ID:
08ef9da445c4b5439c4733e1f35705ba01a2767cb...@mail.cs.mum.edu
Content-Type: text/plain; charset=us-ascii

I have lots of problems with cabal - not sure why or how to correct them.
ghc-pkg check reports tons of issues, but all seem to be haddock-html, which 
doesn't sound too serious, or haddock-interfaces.
   Warning: haddock-html: 
C:\Users\guthrie\AppData\Roaming\cabal\doc\wxdirect-0.90.0.1\html doesn't exist 
or isn't a directory
   ...

Cabal install errors, For example;
   C:\Users\guthriecabal install gloss-examples
   Resolving dependencies...
   Configuring gloss-raster-1.7.4.4...
   Building gloss-raster-1.7.4.4...
   Preprocessing library gloss-raster-1.7.4.4...
   [1 of 2] Compiling Graphics.Gloss.Raster.Array ( 
Graphics\Gloss\Raster\Array.hs, dist\build\Graphics\Gloss\Raster\Array.o )
   Warning: Couldn't figure out LLVM version!
 Make sure you have installed LLVM
   ghc.exe: could not execute: opt

What is LLVM, and do/how I need to install it?

and another (of many) - perhaps unrelated:
C:\Users\guthrie\AppData\Roaming\cabal\bincabal install wxc
   Resolving dependencies...
   command line: cannot satisfy -package Cabal-1.10.2.0:
Cabal-1.10.2.0-db589dd5d526d3111ac2fde0f9ab986c is unusable due to missing 
or recursive dependencies:
  array-0.3.0.2-8e9cd0144e87fa9cc86cc9031631c4f3 base-4.3.1.0-f520cd232cc386
   346843c4a12b63f44b containers-0.4.0.0-18deac99a132f04751d862b77aab136e 
directory
   -1.1.0.0-3a2367d72569467a8af8a231656ff1b8 
filepath-1.2.0.0-f132e9f7703da4e20a47f
   f2b9acf1ea1 old-time-1.0.0.6-445ce39cbcebd38069c25c0f383b728d 
pretty-1.0.1.2-abc
   7c632374e50e1c1927987c2651f0f 
process-1.0.1.5-b3dded8e54a2e13d22af410bdcfafff4
   (use -v for more information)
   cabal: Error: some packages failed to install:
   wxc-0.90.0.3 failed during the configure step. The exception was:
   ExitFailure 1

Trying to resolve them:
   C:\Users\guthrie\AppData\Roaming\cabal\bincabal install base
   Resolving dependencies...
   cabal: internal error: impossible

I've had several others, not sure if they are package specific issues, or some 
larger issue with cabal and libraries.
So I tried to fix them from a suggestion in SO; delete the ~/ghc  ~/cabal 
files and restart cabal, by a cabal install cabal-install.

It gives:
   C:\Users\guthriecabal install cabal-install
  Resolving dependencies...
  In order, the following would be installed:
   deepseq-1.3.0.0 (reinstall) changes: array-0.4.0.0 - 0.3.0.3
   containers-0.4.2.1 (reinstall) changes: array-0.4.0.0 - 0.3.0.3
   old-time-1.0.0.7 (new version)
   directory-1.1.0.2 (reinstall) changes: filepath-1.3.0.0 - 1.2.0.1,
   old-time-1.1.0.0 - 1.0.0.7
   ...
   cabal: The following packages are likely to be broken by the reinstalls:
   time-1.4
   wxdirect-0.90.0.1
   random-1.0.1.1
   haskell-platform-2012.2.0.0
   QuickCheck-2.4.2
   ...
   ghc-7.4.1
   ...
   Cabal-1.14.0
   process-1.1.0.1
   haskell98-1.1.0.1
   haskell-src-1.0.1.4
   

Beginners Digest, Vol 48, Issue 19

2012-06-15 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  HXT and missing or null values (Ian Knopke)
   2.  Difference between Char and Data.Char modules (Ken Overton)
   3. Re:  Difference between Char and Data.Charmodules
  (Stephen Tetley)
   4. Re:  Difference between Char and Data.Charmodules (Brent Yorgey)
   5. Re:  Difference between Char and Data.Char modules (Ken Overton)
   6. Re:  Difference between Char and Data.Charmodules
  (Stephen Tetley)
   7.  the download package fail to install (Song Zhang)


--

Message: 1
Date: Thu, 14 Jun 2012 17:37:06 +0100
From: Ian Knopke ian.kno...@gmail.com
Subject: [Haskell-beginners] HXT and missing or null values
To: beginners@haskell.org
Message-ID:
CAC+f4w=atir2atjwxbwgzjidr3ituxev1suykgmwnwpf2ss...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

I got it. For anyone else running into the problem from my earlier
email, the way to get a null string is as follows:

Replace this line:
second - text  atTag second - x

with this:
second - ((text `orElse` (constA ))  atTag second - x


Fixed program:

data Thing = Thing {first :: String, second :: String}

getThings = atTag thing 
  proc x - do
  first - text  atTag first - x
  second - ((text `orElse` (constA ))  atTag second - x

  returnA - Thing {first = first,second = second}

atTag tag = deep (isElem  hasName tag)

text = getChildren  getText

parseThings str = runX (readString [withValidate no] str  getThings)



--

Message: 2
Date: Thu, 14 Jun 2012 19:05:58 +
From: Ken Overton kover...@lab49.com
Subject: [Haskell-beginners] Difference between Char and Data.Char
modules
To: 'beginners@haskell.org' beginners@haskell.org
Message-ID:
b6368fed4eebe24fac9de115cf5c8c66afe...@exchange04b.lab49.com
Content-Type: text/plain; charset=utf-8

I just started looking at the Happy packag; I get a compile error when 
attempting to build examples/glr/expr-eval:

ExprData.hs:9:8:
Could not find module `Char'
It is a member of the hidden package `haskell98-2.0.0.1'.

ExprData.hs:9 says  ?import Char? and if I change this to ?import Data.Char? it 
compiles correctly (then I get a similar message for System, but when I 
understand Char I expect I will understand this too).

Could someone kindly explain the difference between these two modules? From the 
look of the error, I?m guessing there?s a history lesson involved?

Thanks,

Ken



This email and any attachments may contain information which is confidential 
and/or privileged. The information is intended exclusively for the addressee 
and the views expressed may not be official policy, but the personal views of 
the originator. If you are not the intended recipient, be aware that any 
disclosure, copying, distribution or use of the contents is prohibited. If you 
have received this email and any file transmitted with it in error, please 
notify the sender by telephone or return email immediately and delete the 
material from your computer. Internet communications are not secure and Lab49 
is not responsible for their abuse by third parties, nor for any alteration or 
corruption in transmission, nor for any damage or loss caused by any virus or 
other defect. Lab49 accepts no liability or responsibility arising out of or in 
any way connected to this email.

--

Message: 3
Date: Thu, 14 Jun 2012 20:27:11 +0100
From: Stephen Tetley stephen.tet...@gmail.com
Subject: Re: [Haskell-beginners] Difference between Char and Data.Char
modules
To: Ken Overton kover...@lab49.com
Cc: beginners@haskell.org beginners@haskell.org
Message-ID:
CAB2TPRBB7du-obYwOghjuc=bgczicmtblfxtgec-p-11ksx...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

Char dates from the Haskell 98 specification, before hierarchical
modules were standardised. Data.Char is the newer hierarchical module
- it has been the de facto standard for a long time. Haskell 98 is
still supported by GHC but it is no longer the default - I think you
have to provide flags at the command line to get H98 automatically.

I'm not sure if the GLR (or attribute grammar) bits of Happy are
actively used, so you might expect a few infelicities if you try to
use them.



--

Message: 4
Date: Thu, 14 Jun 2012 15:32:39 -0400
From: Brent Yorgey byor...@seas.upenn.edu
Subject: Re: 

Beginners Digest, Vol 48, Issue 20

2012-06-16 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  the download package fail to install (Henk-Jan van Tuyl)


--

Message: 1
Date: Fri, 15 Jun 2012 23:30:32 +0200
From: Henk-Jan van Tuyl hjgt...@chello.nl
Subject: Re: [Haskell-beginners] the download package fail to
install
To: beginners@haskell.org, Song Zhang vxan...@gmail.com
Message-ID: op.wfyrc6anpz0...@zen5.arnhem.chello.nl
Content-Type: text/plain; charset=iso-8859-15; format=flowed;
delsp=yes

On Fri, 15 Jun 2012 07:53:32 +0200, Song Zhang vxan...@gmail.com wrote:

 Hi
 There is a package for High-level file download based on URLs called
 download, but failed to build on windows, If you don't know it, you can
 refer to hackage first. I compiled in C, but did not get useful massage,
 anyone can help me a little to fix that.
 cabal install download
 get a bad header file

If you give the following command, you have the source code on disk
   cabal unpack download

Try to install, with debug messages:
   cd download-0.3.2
   cabal install -v3

Near the end, you will see:
   cbits/download.h:49:15: error: 'MAXHOSTNAMELEN' undeclared here (not in a
   function)

cbits/download.h uses the macro MAXHOSTNAMELEN; on a Windows system, this
is defined in a different header file,

A simple solution is inserting the following lines after line 44 in  
download.h:
   #ifdef _WIN32
   #define MAXHOSTNAMELEN 256
   #endif

This results in a complaint about macro FILE not being defined; this can  
be solved by adding line:
   #include stddef.h

The error message now is:
   In file included from C:\DOCUME~1\Henk-Jan\LOCALS~1\Temp\1848.c:1:0:
   cbits/download.h:98:1: error: expected '=', ',', ';', 'asm' or  
'__attribute__'
   before 'FILE'

I hope someone else will solve this last(?) problem.

Regards,
Henk-Jan van Tuyl


-- 
http://Van.Tuyl.eu/
http://members.chello.nl/hjgtuyl/tourdemonad.html
Haskell programming
--



--

___
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 48, Issue 20
*


Beginners Digest, Vol 48, Issue 21

2012-06-16 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  about kind of (-) (Song Zhang)
   2. Re:  about kind of (-) (Ertugrul S?ylemez)
   3.  IO - getContents - putStrLn (Robert Heum?ller)
   4. Re:  IO - getContents - putStrLn (Tobias Brandt)
   5. Re:  IO - getContents - putStrLn (Michael Orlitzky)
   6. Re:  IO - getContents - putStrLn (Brandon Allbery)
   7.  Simplify (normalize) symbolic polynom-like   expression
  (Daniel Hlynskyi)
   8. Re:  Simplify (normalize) symbolic polynom-like   expression
  (M?t? Kov?cs)
   9.  problem with type (miro)


--

Message: 1
Date: Sat, 16 Jun 2012 22:25:08 +0800
From: Song Zhang vxan...@gmail.com
Subject: [Haskell-beginners] about kind of (-)
To: beginners@haskell.org
Message-ID:
CACGMEOk6Xcn8J+4KhU1fKh=qyu8t-kebp0j7fo-0x-n9t-l...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

a function has also a kind. According to haskell report 2010 4.1.2 it is *
- * - *, which is easy to understand. However in ghci I type :k (-). the
output is ?? - ? - *. I want to know what do ?? and ? mean. Thanks
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120616/ab48d400/attachment-0001.htm

--

Message: 2
Date: Sat, 16 Jun 2012 16:43:10 +0200
From: Ertugrul S?ylemez e...@ertes.de
Subject: Re: [Haskell-beginners] about kind of (-)
To: beginners@haskell.org
Message-ID: 20120616164310.1b177...@tritium.streitmacht.eu
Content-Type: text/plain; charset=us-ascii

Song Zhang vxan...@gmail.com wrote:

 a function has also a kind. According to haskell report 2010 4.1.2 it
 is * - * - *, which is easy to understand. However in ghci I type :k
 (-). the output is ?? - ? - *. I want to know what do ??  and ?
 mean. Thanks

This has to do with primitive types like Int#.  It basically says that
the input type can be a primitive type, and if it is, then the output
type must also be primitive.

In fact since GHC 7.4 (or perhaps earlier) the kind is

* - * - *

as expected.


Greets,
Ertugrul
-- next part --
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 836 bytes
Desc: not available
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120616/8f2973a5/attachment-0001.pgp

--

Message: 3
Date: Sat, 16 Jun 2012 20:03:36 +0200
From: Robert Heum?ller mail...@heum.de
Subject: [Haskell-beginners] IO - getContents - putStrLn
To: beginners@haskell.org
Message-ID: 20120616200336.7bd388cd@thor
Content-Type: text/plain; charset=US-ASCII

Hi,

this is probably an easy question, but i simply can't figure out, why
this does not work:

import Data.Char

main = do
contents - getContents
putStrLn $ show $ splitcomma contents

splitcomma = split ','

split :: Char - String - [String]
split _  = []
split sp (c:cs)
| c == sp = : rest
| otherwise = (c : head rest) : tail rest
where
   rest = split sp cs

The program compiles and runs without any problems. But there is
absolutely no output, when f.eg. i type hello, world and hit return.
Why would that be?

Thank you very much



--

Message: 4
Date: Sat, 16 Jun 2012 20:10:01 +0200
From: Tobias Brandt tob.bra...@googlemail.com
Subject: Re: [Haskell-beginners] IO - getContents - putStrLn
To: Robert Heum?ller mail...@heum.de
Cc: beginners@haskell.org
Message-ID:
caoowqir7cubjgtwmcixpf9lrm6hrb6zb0gbgivebtt-esqi...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

On 16 June 2012 20:03, Robert Heum?ller mail...@heum.de wrote:
 The program compiles and runs without any problems. But there is
 absolutely no output, when f.eg. i type hello, world and hit return.
 Why would that be?

getContents reads the entire input to the program. Under Linux
you can terminate input with Ctrl-D. If you want to only read
a single line, use getLine.



--

Message: 5
Date: Sat, 16 Jun 2012 14:10:55 -0400
From: Michael Orlitzky mich...@orlitzky.com
Subject: Re: [Haskell-beginners] IO - getContents - putStrLn
To: beginners@haskell.org
Message-ID: 4fdccc2f.4090...@orlitzky.com
Content-Type: text/plain; charset=ISO-8859-1

On 06/16/12 14:03, Robert Heum?ller wrote:
 Hi,
 
 this is probably an easy question, but i simply can't figure out, why
 this does not work:
 
 ...
 
 The program compiles and runs without any problems. But 

Beginners Digest, Vol 48, Issue 23

2012-06-18 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  lambda notation vs function-argument notation in GHCi
  (Ozgur Akgun)
   2. Re:  lambda notation vs function-argument notation in GHCi
  (Morel Pisum)
   3.  how monomorphism restriction effects eta reduction (Song Zhang)
   4. Re:  problem with type (miro)


--

Message: 1
Date: Sun, 17 Jun 2012 11:28:26 +0100
From: Ozgur Akgun ozgurak...@gmail.com
Subject: Re: [Haskell-beginners] lambda notation vs function-argument
notation in GHCi
To: Morel Pisum morel.pi...@googlemail.com
Cc: beginners@haskell.org
Message-ID:
CALzazPB6uvufwkU4192-=dLOZDBRfpV62tjs3dhbh-SXecO=q...@mail.gmail.com
Content-Type: text/plain; charset=utf-8

http://www.haskell.org/haskellwiki/Monomorphism_restriction

On 17 June 2012 08:13, Morel Pisum morel.pi...@googlemail.com wrote:

 Let's define a function in GHCi:

  Prelude let f s n = and (map (==s) n)
  Prelude :t f
  f :: Eq a = a - [a] - Bool

 This is fine. But when I define this function using lambda notation, I
 get this

  Prelude let f = \s n - and (map (==s) n)
  Prelude :t f
  f :: () - [()] - Bool

 which is really weird.

 Why does this happen?

 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners




-- 
Ozgur Akgun
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120617/ec5d2b65/attachment-0001.htm

--

Message: 2
Date: Sun, 17 Jun 2012 12:37:22 +0200
From: Morel Pisum morel.pi...@googlemail.com
Subject: Re: [Haskell-beginners] lambda notation vs function-argument
notation in GHCi
To: Ozgur Akgun ozgurak...@gmail.com
Cc: beginners@haskell.org
Message-ID: 4fddb362.9000...@googlemail.com
Content-Type: text/plain; charset=UTF-8

Ah, of course! I didn't think I will ever stumble upon this?

Thank you!

 http://www.haskell.org/haskellwiki/Monomorphism_restriction

 On 17 June 2012 08:13, Morel Pisum morel.pi...@googlemail.com wrote:

 Let's define a function in GHCi:

 Prelude let f s n = and (map (==s) n)
 Prelude :t f
 f :: Eq a = a - [a] - Bool
 This is fine. But when I define this function using lambda notation, I
 get this

 Prelude let f = \s n - and (map (==s) n)
 Prelude :t f
 f :: () - [()] - Bool
 which is really weird.

 Why does this happen?




--

Message: 3
Date: Mon, 18 Jun 2012 00:22:40 +0800
From: Song Zhang vxan...@gmail.com
Subject: [Haskell-beginners] how monomorphism restriction effects eta
reduction
To: beginners@haskell.org
Message-ID:
cacgmeonsqaagoaaztaij7fhkhcrvpykttw8k5fsjfa8k9m5...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

I think monomorphism restriction is for shared evaluation.like following
function
f xs = let len = genericLength xs in (len, len) from haskell wiki
under monomorphism the type is Num t = [b] - (t, t), if it no
monomorphism restriction the type will be (Num t, Num t1) = [b] - (t, t1)
which lead to twice evaluation of len. However I didn't see how the
restriction effects eta reduction, when define function like f = show, g =
(==) or f = \x - show x, g = \x - \y - (x==y). anyone can explain it to
me? Thanks a lot.
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120618/d507517c/attachment-0001.htm

--

Message: 4
Date: Sun, 17 Jun 2012 20:53:35 +0200
From: miro miroslav.kar...@gmail.com
Subject: Re: [Haskell-beginners] problem with type
To: beginners@haskell.org
Message-ID: 4fde27af.1020...@gmail.com
Content-Type: text/plain; charset=iso-8859-1; Format=flowed

Thank you!

Miro


On 6/17/12 9:08 AM, Morel Pisum wrote:
 What you want is probably

 checkNode :: String -  [String] -  Bool
 checkNode s nodes = and (map (==s) nodes)

 which returns True iff all nodes equal s.


 Am a bit stuck here,... please, what is wrong with this?

 checkNode :: String -  [String] -  Bool
 checkNode s nodes =
 [s == node | node- nodes ]


 src/me.hs:3:4:
  Couldn't match expected type `Bool' with actual type `[t0]'
 [1 of 1] Compiling Main ( src/me.hs, interpreted )
  In the expression: [s == node | node- nodes]
 Failed, modules loaded: none.
  In an equation for `checkNode':
  checkNode s nodes = [s == node | node- nodes]

 

Beginners Digest, Vol 48, Issue 24

2012-06-19 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  Improving Performance (Robert Heum?ller)
   2. Re:  General Hints on Improving Performance - Example DBSCAN
  (Robert Heum?ller)
   3. Re:  Improving Performance (Ertugrul S?ylemez)
   4. Re:  Improving Performance (Robert Heum?ller)
   5.  Understanding how laziness works (Matt Ford)
   6. Re:  Improving Performance (Robert Heum?ller)
   7. Re:  Improving Performance (Ertugrul S?ylemez)
   8. Re:  Understanding how laziness works (Alexander Batischev)
   9.  Function application versus function composition performance
  (Matt Ford)


--

Message: 1
Date: Tue, 19 Jun 2012 16:37:57 +0200
From: Robert Heum?ller mail...@heum.de
Subject: [Haskell-beginners] Improving Performance
To: beginners@haskell.org
Message-ID: 20120619163757.1c528917@thor
Content-Type: text/plain; charset=US-ASCII

Hello,

in order to tune my brain to functional thinking I've decided to
start writing some real programs. After having spent a couple of days
figuring out how to translate an imperative algorithm into stateless
haskell I beleive I've now managed a simple implementation of the DBSCAN
clustering algorithm.

http://privatepaste.com/e6bb4fb665

This code has several drawbacks (and probably it doesn't work correctly
after all) but I would like to tune its performance.
Obviously the code calls several functions multiply with the same
arguments. Haskell, being stateless should thus always yield the same
resuts, correct? In this case performing the same calculations multiply
seems pointless.

My question: 
How would you go about improving this code? 
In any imperative language I would simply cache distances/neighborhoods
in a matrix. Obviously this is not what the way to go in haskell?

Thank you very much



--

Message: 2
Date: Tue, 19 Jun 2012 16:45:51 +0200
From: Robert Heum?ller mail...@heum.de
Subject: Re: [Haskell-beginners] General Hints on Improving
Performance - Example DBSCAN
To: beginners@haskell.org
Message-ID: 20120619164551.5a2a337e@thor
Content-Type: text/plain; charset=US-ASCII

I'm sorry the Thread title is not very helpful... I hope this is better


 Hello,
 
 in order to tune my brain to functional thinking I've decided to
 start writing some real programs. After having spent a couple of
 days figuring out how to translate an imperative algorithm into
 stateless haskell I beleive I've now managed a simple implementation
 of the DBSCAN clustering algorithm.
 
 http://privatepaste.com/e6bb4fb665
 
 This code has several drawbacks (and probably it doesn't work
 correctly after all) but I would like to tune its performance.
 Obviously the code calls several functions multiply with the same
 arguments. Haskell, being stateless should thus always yield the same
 resuts, correct? In this case performing the same calculations
 multiply seems pointless.
 
 My question: 
 How would you go about improving this code? 
 In any imperative language I would simply cache
 distances/neighborhoods in a matrix. Obviously this is not what the
 way to go in haskell?
 
 Thank you very much
 
 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners




--

Message: 3
Date: Tue, 19 Jun 2012 17:01:26 +0200
From: Ertugrul S?ylemez e...@ertes.de
Subject: Re: [Haskell-beginners] Improving Performance
To: beginners@haskell.org
Message-ID: 20120619170126.5c4b5...@tritium.streitmacht.eu
Content-Type: text/plain; charset=utf-8

Robert Heum?ller mail...@heum.de wrote:

 in order to tune my brain to functional thinking I've decided to
 start writing some real programs. After having spent a couple of
 days figuring out how to translate an imperative algorithm into
 stateless haskell I beleive I've now managed a simple implementation
 of the DBSCAN clustering algorithm.

 http://privatepaste.com/e6bb4fb665

When asking people to review your code, it would be very helpful to
write type signatures for your top-level functions.  This alone makes
code greatly more readable and also tells a lot about the quality right
away.  I advice you to get used to writing type signatures for yourself
as well.


Greets,
Ertugrul

-- 
Not to be or to be and (not to be or to be and (not to be or to be and
(not to be or to be and ... that is the list monad.
-- next part --
A non-text attachment was scrubbed...
Name: 

Beginners Digest, Vol 48, Issue 25

2012-06-20 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  Function application versus function composition
  performance (KC)
   2. Re:  Function application versus function composition
  performance (Ertugrul S?ylemez)


--

Message: 1
Date: Tue, 19 Jun 2012 15:08:31 -0700
From: KC kc1...@gmail.com
Subject: Re: [Haskell-beginners] Function application versus function
composition performance
To: Matt Ford m...@dancingfrog.co.uk, beginners@haskell.org,
haskell-cafe haskell-c...@haskell.org
Message-ID:
camlkxymbnwy89vvofp6pec7g-pwtwsvc54veg5bnem3ytnr...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

A good functional programming language has a good code algebra after
parsing to which algebraic transformations can be applied for optimization.

For example, reducing the need for generating intermediate data structures.

See: fusion.



On Tue, Jun 19, 2012 at 3:01 PM, Matt Ford m...@dancingfrog.co.uk wrote:

 Hi All,

 My last question got me thinking (always dangerous): an expression
 that doubles a list and takes the 2nd element (index 1), I assume,
 goes through the following steps.

 double (double [1,2,3,4]) !! 1
 double ( 1*2 : double [2,3,4]) !! 1
 1*2*2 : double ( double [2,3,4] ) !! 1
 1*2*2 : double ( 2*2 : double [3,4] ) !! 1
 1*2*2 : 2*2*2 : double ( double [3,4] ) !! 1
 2*2*2
 8

 Up until the element requested all the proceeding elements have to
 have the expression formed as Haskell process the calculation.

 Now, I want to compare this to using function composition

 ( double . double ) [ 1 ,2, 3, 4 ] !! 1

 This is the bit I'm unsure of - what does the composition look like.
 It is easy to see that it could be simplified to something like:

 ( double . double) (x:xs) = x*4 : (double . double) xs

 This would mean the steps could be written

 (double . double) [ 1,2,3,4 ] !! 1
 (1*4 : (double.double) [2,3,4]) !! 1
 (1*4 : 2*4 : (double.double) [ 3,4 ]) !! 1
 2*4
 8

 Ignoring the start and end steps, it will be half the number of steps
 compared to the application version.  Significant then, over long
 lists.

 So is this true, are composite functions simplified in Haskell in
 general so that they may have improved performance over function
 application?

 I've seen posts on the internet that say it's a matter of style only:

 http://stackoverflow.com/questions/3030675/haskell-function-composition-and-function-application-idioms-correct-us
 .
  But my reasoning suggests it could be more than that.

 Perhaps, function application is similarly optimised - maybe by
 replacing all functions applications with composition and then
 simplifying?  Or maybe the simplifying/optimisation step never
 happens?  As you can see I'm just guessing at things :-)  But it's
 nice to wonder.

 Many thanks for any pointers,

 Matt.

 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners




-- 
--
Regards,
KC
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120619/7c7dcd4d/attachment-0001.htm

--

Message: 2
Date: Wed, 20 Jun 2012 01:10:03 +0200
From: Ertugrul S?ylemez e...@ertes.de
Subject: Re: [Haskell-beginners] Function application versus function
composition performance
To: beginners@haskell.org
Message-ID: 20120620011003.2d5e3...@tritium.streitmacht.eu
Content-Type: text/plain; charset=us-ascii

Matt Ford m...@dancingfrog.co.uk wrote:

 So is this true, are composite functions simplified in Haskell in
 general so that they may have improved performance over function
 application?

You may be forgetting that Haskell is lazily evaluated.  If you have
seen the output of compilers for strict languages like C you may find
yourself somewhere between surprised and shocked to see what a Haskell
compiler produces.  The result is not a set of procedures, but a graph
and the less nodes the higher the performance.

To answer your question:  A completely naive compiler will produce the
most efficient code for function application.  That's three nodes, one
for the application node, one for the function, one for the argument.
In that sense function application is in a sense an atom.  In the case
of applying two functions the result will be five nodes.

On the other hand the function composition operator is compiled to what
is called a supercombinator.  

Beginners Digest, Vol 48, Issue 27

2012-06-26 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  darcsden (Jack Henahan)
   2. Re:  darcsden (Rui Barreiro)


--

Message: 1
Date: Mon, 25 Jun 2012 13:31:27 -0400
From: Jack Henahan jhena...@uvm.edu
Subject: Re: [Haskell-beginners] darcsden
To: Rui Barreiro rui.barre...@gmail.com
Cc: beginners@haskell.org
Message-ID: 52e42b77-0b6b-4482-80d7-4905a3b4d...@uvm.edu
Content-Type: text/plain; charset=iso-8859-1

Do you get different results if you use `cabal install darcsden 
--solver=modular --avoid-reinstalls`?
On Jun 21, 2012, at 6:51 PM, Rui Barreiro wrote:

 I would like to install darcsden on my machine, but I am having some 
 difficulties. When I make cabal install I get this message:
 
 cabal: The following packages are likely to be broken by the reinstalls:
 bin-package-db-0.0.0.0
 ghc-7.4.1
 Use --force-reinstalls if you want to install anyway.
 
 what should I do? and why?
 
 Thanks
  
 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners

-- next part --
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 841 bytes
Desc: Message signed with OpenPGP using GPGMail
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120625/25aa0751/attachment-0001.pgp

--

Message: 2
Date: Mon, 25 Jun 2012 23:21:47 +0100
From: Rui Barreiro rui.barre...@gmail.com
Subject: Re: [Haskell-beginners] darcsden
To: Jack Henahan jhena...@uvm.edu
Cc: beginners@haskell.org
Message-ID:
ca+zr+nfn1worfuss5qboiffgdaeel-xmamjqlkp19iwae12...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

I get the same error as with --force-reinstalls which is

src/SSH/Crypto.hs:145:55:
Not in scope: data constructor `RSA.PrivateKey'

It seams to me that some code is based on an older version of
Codec.Crypto.RSA.

On Mon, Jun 25, 2012 at 6:31 PM, Jack Henahan jhena...@uvm.edu wrote:

 Do you get different results if you use `cabal install darcsden
 --solver=modular --avoid-reinstalls`?
 On Jun 21, 2012, at 6:51 PM, Rui Barreiro wrote:

  I would like to install darcsden on my machine, but I am having some
 difficulties. When I make cabal install I get this message:
 
  cabal: The following packages are likely to be broken by the reinstalls:
  bin-package-db-0.0.0.0
  ghc-7.4.1
  Use --force-reinstalls if you want to install anyway.
 
  what should I do? and why?
 
  Thanks
 
  ___
  Beginners mailing list
  Beginners@haskell.org
  http://www.haskell.org/mailman/listinfo/beginners


-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120625/b4eee8dd/attachment-0001.htm

--

___
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 48, Issue 27
*


Beginners Digest, Vol 48, Issue 28

2012-06-27 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  No accumulation of partially applied functions   allowed?
  (Obscaenvs)
   2. Re:  No accumulation of partially applied functions allowed?
  (Brent Yorgey)
   3. Re:  No accumulation of partially applied functions allowed?
  (Jay Sulzberger)
   4. Re:  No accumulation of partially applied functions allowed?
  (Alec Story)
   5. Re:  No accumulation of partially applied functions allowed?
  (Jay Sulzberger)


--

Message: 1
Date: Tue, 26 Jun 2012 22:08:49 +0200
From: Obscaenvs obscae...@gmail.com
Subject: [Haskell-beginners] No accumulation of partially applied
functions   allowed?
To: beginners@haskell.org
Message-ID: 4fea16d1.3030...@gmail.com
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Sorry if this is a less than stellar question.

The problem:
Given a function f :: a - a - a - b, make it work on a list instead: 
f `applyTo`[x,y,z] where [x,y,z] :: [a].
My stab at a general solution was
`
applyTo f [] = error no arg
applyTo f (x:xs) = go (f x) xs
 where
   go acc [] = acc
   go acc (y:[]) = acc y
   go acc (y:ys) = go (acc $ y) ys
`

I thought this would work, functions being first class citizens but 
ghci complains:
 Occurs check: cannot construct the infinite type: t1 = t0 - t1
 In the return type of a call of `acc'
 Probable cause: `acc' is applied to too many arguments
 In the expression: acc y
 In an equation for `go': go acc (y : []) = acc y

The 'probable cause' isn't the real cause here, but something to do with 
the fact that it's impossible to accumulate functions in this way...
Or am I just too tired too make it work? I can see that the type of `go` 
could be a problem, but is it insurmountable?

/F



--

Message: 2
Date: Tue, 26 Jun 2012 16:59:29 -0400
From: Brent Yorgey byor...@seas.upenn.edu
Subject: Re: [Haskell-beginners] No accumulation of partially applied
functions allowed?
To: beginners@haskell.org
Message-ID: 20120626205929.ga9...@seas.upenn.edu
Content-Type: text/plain; charset=us-ascii

On Tue, Jun 26, 2012 at 10:08:49PM +0200, Obscaenvs wrote:
 Sorry if this is a less than stellar question.
 
 The problem:
 Given a function f :: a - a - a - b, make it work on a list
 instead: f `applyTo`[x,y,z] where [x,y,z] :: [a].
 My stab at a general solution was
 `
 applyTo f [] = error no arg
 applyTo f (x:xs) = go (f x) xs
 where
   go acc [] = acc
   go acc (y:[]) = acc y
   go acc (y:ys) = go (acc $ y) ys
 `
 
 I thought this would work, functions being first class citizens but
 ghci complains:
 Occurs check: cannot construct the infinite type: t1 = t0 - t1
 In the return type of a call of `acc'
 Probable cause: `acc' is applied to too many arguments
 In the expression: acc y
 In an equation for `go': go acc (y : []) = acc y
 
 The 'probable cause' isn't the real cause here, but something to do
 with the fact that it's impossible to accumulate functions in this
 way...
 Or am I just too tired too make it work? I can see that the type of
 `go` could be a problem, but is it insurmountable?

The type of `go` is exactly the problem.  In particular, the type of
acc's first parameter.  In the third clause of go's definition, we can
see that `acc` and (acc $ y) are both used as the first argument to
go, hence they must have the same type.  However, this is impossible
-- if acc has type (t0 - t1), then y must have type t0, and (acc $ y)
has type t1, so it would have to be the case that t1 = t0 - t1 --
hence the error message.

It is not possible in Haskell to define `applyTo`.* I know this
function gets used a lot in lisp/scheme, but Haskell style is
different.  If you explain the context in which you wanted this
function, perhaps we can help you figure out a better way to structure
things so it is not needed.

-Brent

* At least not without crazy type class hackery.



--

Message: 3
Date: Tue, 26 Jun 2012 17:19:28 -0400 (EDT)
From: Jay Sulzberger j...@panix.com
Subject: Re: [Haskell-beginners] No accumulation of partially applied
functions allowed?
To: beginners@haskell.org
Message-ID: pine.neb.4.64.1206261705430.4...@panix3.panix.com
Content-Type: TEXT/PLAIN; charset=US-ASCII; format=flowed



On Tue, 26 Jun 2012, Brent Yorgey byor...@seas.upenn.edu wrote:

 On Tue, Jun 26, 2012 at 10:08:49PM +0200, Obscaenvs wrote:
 Sorry if this is a 

Beginners Digest, Vol 48, Issue 29

2012-06-28 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  No accumulation of partially applied functions allowed?
  (ARJANEN Lo?c Jean David)
   2. Re:  No accumulation of partially applied functions allowed?
  (Brent Yorgey)


--

Message: 1
Date: Wed, 27 Jun 2012 14:01:10 +0200
From: ARJANEN Lo?c Jean David arjanen.l...@gmail.com
Subject: Re: [Haskell-beginners] No accumulation of partially applied
functions allowed?
To: beginners@haskell.org
Message-ID:
cab2q81ax8fy6xq5kvwweacq5ovdxj27ym+wrmbjgsh70g7-...@mail.gmail.com
Content-Type: text/plain; charset=utf-8

It is easy, but inconvenient to define applyTo on tuples, which are
Haskell's standard container for heterogeneous collections (that would
basically be an extension of Prelude's uncurry), but they would be
inconvenient to define and quite unwieldy to use.

If you limit yourself to homogeneous collections (that is, lists), it's
possible but using typeclass hackery and you shouldn't do so unless you
need to. for an example of such techniques, see
HaXRhttp://www.haskell.org/haskellwiki/HaXR
or hs-json-rpc http://hackage.haskell.org/package/hs-json-rpc where this
kind of tricks are used to implement remote calls.

2012/6/27  Jay Sulzberger:

 On Tue, 26 Jun 2012, Alec Story av...@cornell.edu wrote:

 Because of Haskell's type system, there are some expressions that you
 simply cannot compile.  Most of them you don't *want* to compile because
 they do bad things (like add two strings, for example).  Some things are
 legal in Lisp but don't typecheck in Haskell for exactly the reasons that
 Brent pointed out.  They might make sense in some contexts, but the
 compiler isn't able to reason about them.


 Thanks, Alec.

 What is a formalized version of

  It is not possible in Haskell to define `applyTo`.*
  * At least not without crazy type class hackery.

 I think the difficulty must arise mainly from the *, meaning I
 think, any type in the above `applyTo`.*.  Would it be
 easy/convenient to define `applyTo`.(a, b, c) where a is a type
 variable?  In general can we, for any finite number n, where n  2,
 easily/conveniently define `applyTo`.(a1, a2, ..., an) ?

 Ah, I see that the problem is for lists of length 3, so for the
 type, if it be such, that I might write as [a, a, a], ah, OK, I
 will fire up GHCi and have a look.

 oo--JS.



 On Tue, Jun 26, 2012 at 5:19 PM, Jay Sulzberger j...@panix.com wrote:



 On Tue, 26 Jun 2012, Brent Yorgey byor...@seas.upenn.edu wrote:

  On Tue, Jun 26, 2012 at 10:08:49PM +0200, Obscaenvs wrote:


 Sorry if this is a less than stellar question.

 The problem:
 Given a function f :: a - a - a - b, make it work on a list
 instead: f `applyTo`[x,y,z] where [x,y,z] :: [a].
 My stab at a general solution was
 `
 applyTo f [] = error no arg
 applyTo f (x:xs) = go (f x) xs
   where
 go acc [] = acc
 go acc (y:[]) = acc y
 go acc (y:ys) = go (acc $ y) ys
 `

 I thought this would work, functions being first class citizens but
 ghci complains:
   Occurs check: cannot construct the infinite type: t1 = t0 - t1
   In the return type of a call of `acc'
   Probable cause: `acc' is applied to too many arguments
   In the expression: acc y
   In an equation for `go': go acc (y : []) = acc y

 The 'probable cause' isn't the real cause here, but something to do
 with the fact that it's impossible to accumulate functions in this
 way...
 Or am I just too tired too make it work? I can see that the type of
 `go` could be a problem, but is it insurmountable?


 The type of `go` is exactly the problem.  In particular, the type of
 acc's first parameter.  In the third clause of go's definition, we can
 see that `acc` and (acc $ y) are both used as the first argument to
 go, hence they must have the same type.  However, this is impossible
 -- if acc has type (t0 - t1), then y must have type t0, and (acc $ y)
 has type t1, so it would have to be the case that t1 = t0 - t1 --
 hence the error message.

 It is not possible in Haskell to define `applyTo`.* I know this
 function gets used a lot in lisp/scheme, but Haskell style is
 different.  If you explain the context in which you wanted this
 function, perhaps we can help you figure out a better way to structure
 things so it is not needed.

 -Brent

 * At least not without crazy type class hackery.


 What is the difficulty?

 Is the difficulty at the level of syntax?

 Or is it that the type Haskell expression, perhaps Haskell
 form, to use an 

Beginners Digest, Vol 48, Issue 30

2012-06-29 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  test-framework (Mateusz Neumann)
   2. Re:  test-framework (Mateusz Neumann)
   3.  Help with Why Do Monads Matter blog post understanding
  (Matt Ford)


--

Message: 1
Date: Fri, 29 Jun 2012 07:30:23 +0200
From: Mateusz Neumann mate...@neumanny.net
Subject: [Haskell-beginners] test-framework
To: beginners@haskell.org
Message-ID: 20120629073023.03c72439@dragonfly.localdomain
Content-Type: text/plain; charset=us-ascii

Hi,

I am currently writing testing routines for my project.  I have came
across an interesting test-framework
(http://hackage.haskell.org/package/test-framework-0.6).  Do you know
it?  I use QuickCheck2 provider (Test.Framework.Providers.QuickCheck2)
to property tests.  And here is my problem: I find configuring the
provider very confusing, I cannot set (in Haskell code) for example
number of tests to run or other QuickCheck parameters.  Could you
please help?

Thanks

-- 
Mateusz
-- next part --
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 230 bytes
Desc: not available
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120629/5ff5a066/attachment-0001.pgp

--

Message: 2
Date: Fri, 29 Jun 2012 09:58:34 +0200
From: Mateusz Neumann mate...@neumanny.net
Subject: Re: [Haskell-beginners] test-framework
To: Lorenzo Bolla lbo...@gmail.com, beginners@haskell.org
Message-ID: 20120629095834.7208a123@dragonfly.localdomain
Content-Type: text/plain; charset=us-ascii

On Fri, 29 Jun 2012 08:43:33 +0100
Lorenzo Bolla lbo...@gmail.com wrote:

 Are the examples in the package distribution of any help?
 https://github.com/batterseapower/test-framework/blob/master/example/Test/Framework/Example.lhs
 
 L.

I was thinking more about parametres set in Haskell code itself.  There
is something like TestOptions
(http://hackage.haskell.org/packages/archive/test-framework/0.6/doc/html/Test-Framework-Options.html#t:TestOptions)
and RunnerOptions
(http://hackage.haskell.org/packages/archive/test-framework/0.6/doc/html/Test-Framework-Runners-Options.html)
but I do not find any examples of using them.  Similarly, I do not know
how to set them up.


 On Fri, Jun 29, 2012 at 6:30 AM, Mateusz Neumann
 mate...@neumanny.netwrote:
 
  Hi,
 
  I am currently writing testing routines for my project.  I have came
  across an interesting test-framework
  (http://hackage.haskell.org/package/test-framework-0.6).  Do you
  know it?  I use QuickCheck2 provider
  (Test.Framework.Providers.QuickCheck2) to property tests.  And here
  is my problem: I find configuring the provider very confusing, I
  cannot set (in Haskell code) for example number of tests to run or
  other QuickCheck parameters.  Could you please help?
 
  Thanks
 
  --
  Mateusz
 
  ___
  Beginners mailing list
  Beginners@haskell.org
  http://www.haskell.org/mailman/listinfo/beginners
 
 



-- 
Mateusz
-- next part --
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 230 bytes
Desc: not available
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120629/07b87fea/attachment-0001.pgp

--

Message: 3
Date: Fri, 29 Jun 2012 09:57:42 +0100
From: Matt Ford m...@dancingfrog.co.uk
Subject: [Haskell-beginners] Help with Why Do Monads Matter blog post
understanding
To: beginners@haskell.org
Message-ID: 20120629085741.gm20...@rss01.mhs.man.ac.uk
Content-Type: text/plain; charset=utf-8

Hi,

I've been reading the following blog post

https://cdsmith.wordpress.com/2012/04/18/why-do-monads-matter/

And I think I like it.  But there's a part that I don't get.

For a set A, we will define the set Pref(A) to be the set of functions
from application settings to the set A. Now watch closely: a function in
context from A to B is just an ordinary function from A to Pref(B). In
other words, you give it a value from the set A, and it gives you back
another function that maps from application settings to the set B.

This is in the functioning with dependency section and is talking about a
procedure that uses outside info from preferences or application settings.

If I set my prefs as follows

configvar = 3

and define a function as follows

add x = configvar + 6

So add?s signature is

add: int - int

What does prefs(int) look like? Is that even the 

Beginners Digest, Vol 48, Issue 31

2012-06-30 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  FRP and a set of pairwise interacting(colliding) objects
  (Nathan H?sken)
   2. Re:  FRP and a set of pairwise interacting(colliding)
  objects (Ertugrul S?ylemez)
   3. Re:  test-framework (Michael Orlitzky)
   4. Re:  Help with Why Do Monads Matter blog post understanding
  (Brent Yorgey)
   5. Re:  Help with Why Do Monads Matter blog post understanding
  (Matt Ford)
   6. Re:  test-framework (Mateusz Neumann)
   7. Re:  Help with Why Do Monads Matter blog post understanding
  (Paulo Pocinho)
   8. Re:  FRP and a set of pairwise interacting (colliding)
  objects (Nathan H?sken)


--

Message: 1
Date: Fri, 29 Jun 2012 14:07:13 +0200
From: Nathan H?sken nathan.hues...@posteo.de
Subject: [Haskell-beginners] FRP and a set of pairwise interacting
(colliding) objects
To: beginners@haskell.org
Message-ID: 4fed9a71.2070...@posteo.de
Content-Type: text/plain; charset=ISO-8859-1

Hi,

I want to simulate as set of 2D objects, which can collide pairs wise
with each other.
In an OOP language, I would do this:

  for (o1 in objects) {
for (o2 in objets) {
  if (testCollision(o1, o2)) {
CollData cd = getCollisionData(o1,o2);
o1.reactToCollision(cd);
o2.reactToCollision(cd):
  }
}
  }

Now I want to do the same thing in Haskell with FRP.
Normally in FRP (correct me if I am wrong) I have for my objects a
Signal (or whatever it is called in the specific library), which gets as
input the collision events for this object (and probably more data, but
let's assume collision events are enough):

  object :: Signal (Event CollData) ObjectState

The CollData events themself are generated at another place:

  collisions :: Signal [ObjectState] (Event CollData)

But now the collisions are generated at one place, and processed at
another. This means that CollData must be somehow tagged to the objects
it belongs to (an ID for example). This again means that some function
must take the pool of all collision datas and distribute them to the
object Signals.

When I have a lot of objects, this means a significant overhead!

Now I am wondering if there is a nicer approach which avoids this overhead.

Thanks!
Nathan



--

Message: 2
Date: Fri, 29 Jun 2012 16:47:44 +0200
From: Ertugrul S?ylemez e...@ertes.de
Subject: Re: [Haskell-beginners] FRP and a set of pairwise interacting
(colliding) objects
To: beginners@haskell.org
Message-ID: 20120629164744.0c5cf...@angst.streitmacht.eu
Content-Type: text/plain; charset=utf-8

Nathan H?sken nathan.hues...@posteo.de wrote:

 [...]

 But now the collisions are generated at one place, and processed at
 another. This means that CollData must be somehow tagged to the
 objects it belongs to (an ID for example). This again means that some
 function must take the pool of all collision datas and distribute them
 to the object Signals.

 When I have a lot of objects, this means a significant overhead!

 Now I am wondering if there is a nicer approach which avoids this
 overhead.

You can get around the overhead by letting the objects do the collisions
themselves, much like in your OOP variant.  For instance in Netwire you
could have this:

planets :: MyWire [Planet] Planet

This naive way still causes the overhead of lists and a planet
distinguishing between others and itself.  But now this is simply a
matter of choosing proper data structures and starting to identify
planets:

type PlanetSet = Map PlanetId Planet

planets :: MyWire PlanetSet (PlanetId, Planet)

This looks more promising.  Now the last thing is that this looks like a
chicken/egg problem, but it's easy to resolve using ArrowLoop and
one-instant delays.


Greets,
Ertugrul

-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/
-- next part --
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 836 bytes
Desc: not available
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120629/af3e6653/attachment-0001.pgp

--

Message: 3
Date: Fri, 29 Jun 2012 11:50:13 -0400
From: Michael Orlitzky mich...@orlitzky.com
Subject: Re: [Haskell-beginners] test-framework
To: beginners@haskell.org
Message-ID: 4fedceb5.2010...@orlitzky.com
Content-Type: text/plain; charset=UTF-8

On 06/29/12 03:58, Mateusz Neumann wrote:
 On Fri, 29 Jun 

Beginners Digest, Vol 49, Issue 1

2012-07-01 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  Concurrent vs GHC (Mauricio Hernandes)
   2. Re:  Concurrent vs GHC (Felipe Almeida Lessa)
   3. Re:  Concurrent vs GHC (Mauricio Hernandes)


--

Message: 1
Date: Sun, 1 Jul 2012 00:03:34 +0900
From: Mauricio Hernandes maukeshig...@gmail.com
Subject: [Haskell-beginners] Concurrent vs GHC
To: beginners@haskell.org
Message-ID:
caoons7zurxzpyejxp-wxlutfbx+jdstrhfnvaq2+5w8f9_r...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

Hello, I'm having a problem with GHC.

When I compile the code bellow it does nothing, but If I try to use ghci it
works normally.

it seems a simple problem, but I can't understand.

Thanks for the help

Mauricio


import System.IO
import Control.Concurrent
import Data.List

main = do
 input - newMVar  [1..3]
 ia - newEmptyMVar
 ib - newEmptyMVar
 ic - newEmptyMVar

 forkIO $ do x - readMVar input
 putMVar ia x

 forkIO $ do a - readMVar ia
 putMVar ib ( sum a )

 forkIO $ do a - readMVar ia
 putMVar ic ( reverse a )

 forkIO $ do b - readMVar ib
 c - readMVar ic
 print b
 print c
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120701/712d04f7/attachment-0001.htm

--

Message: 2
Date: Sat, 30 Jun 2012 12:24:02 -0300
From: Felipe Almeida Lessa felipe.le...@gmail.com
Subject: Re: [Haskell-beginners] Concurrent vs GHC
To: maukeshig...@gmail.com
Cc: beginners@haskell.org
Message-ID:
CANd=ogeerxzpn116cqlpoddvassuebynwrbrg2tp4j3q9ob...@mail.gmail.com
Content-Type: text/plain; charset=UTF-8

Your application is exiting before your forkIOs get a chance to
execute.  Instead of

  forkIO $ do
...
  forkIO $ do
...
  forkIO $ do
...

use something like

  finished - newEmptyMVar

  forkIO $ do
...
putMVar finished ()

  forkIO $ do
...
putMVar finished ()

  forkIO $ do
...
putMVar finished ()

  replicateM_ 3 (takeMVar finished)

Doing so will avoid your program to exit until all threads have finished.

Note that the code above is extremely fragile: doesn't handle
exceptions, you have to manually specify the number of threads that
you opened, etc.  These are abstracted by some libraries on Hackage
that you may use later for Real World Code (TM).

Cheers, =)

-- 
Felipe.



--

Message: 3
Date: Sun, 1 Jul 2012 02:51:27 +0900
From: Mauricio Hernandes maukeshig...@gmail.com
Subject: Re: [Haskell-beginners] Concurrent vs GHC
To: Felipe Almeida Lessa felipe.le...@gmail.com
Cc: beginners@haskell.org
Message-ID:
CAOons7a6j9Mws-CTHJvRr5zHFQXmVX7-tpzq=xt0hpnjoej...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

Eternal Gratitude for the help, it's working perfectly, I will consider the
exceptions and other stuff now.

the code looks like this now


import System.IO
import Control.Concurrent
import Data.List
import Control.Monad

main = do
  finished - newEmptyMVar
  input - newMVar  [1..3]
  ia - newEmptyMVar
  ib - newEmptyMVar
  ic - newEmptyMVar

  forkIO $ do x - readMVar input
  putMVar ia x
  putMVar finished ()

  forkIO $ do a - readMVar ia
  putMVar ib ( sum a )
  putMVar finished ()

  forkIO $ do a - readMVar ia
  putMVar ic ( reverse a )
  putMVar finished ()

  b - readMVar ib
  c - readMVar ic
  writeFile somaEprod.txt (show b ++ \n)
  appendFile somaEprod.txt (show c)
  replicateM_ 3 (takeMVar finished)




Valeu
Mauricio

On Sun, Jul 1, 2012 at 12:24 AM, Felipe Almeida Lessa 
felipe.le...@gmail.com wrote:

 Your application is exiting before your forkIOs get a chance to
 execute.  Instead of

  forkIO $ do
...
  forkIO $ do
...
  forkIO $ do
...

 use something like

  finished - newEmptyMVar

  forkIO $ do
...
putMVar finished ()

  forkIO $ do
...
putMVar finished ()

  forkIO $ do
...
putMVar finished ()

  replicateM_ 3 (takeMVar finished)

 Doing so will avoid your program to exit until all threads have finished.

 Note that the code above is extremely fragile: doesn't handle
 exceptions, you have to 

Beginners Digest, Vol 49, Issue 4

2012-07-03 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  Functional Parses (Robert Heum?ller)
   2. Re:  Functional Parses (Robert Heum?ller)
   3. Re:  Functional Parses (Christian Maeder)
   4.  Using tls-extra for simple smtp (Sarfraz K.)
   5. Re:  Functional Parses (Stephen Tetley)
   6.  Problems with installing lambdabot (Antoras)
   7. Re:  Problems with installing lambdabot (Brent Yorgey)
   8. Re:  Help with Why Do Monads Matter blog post understanding
  (Brent Yorgey)


--

Message: 1
Date: Tue, 3 Jul 2012 15:08:37 +0200
From: Robert Heum?ller mail...@heum.de
Subject: [Haskell-beginners] Functional Parses
To: beginners@haskell.org
Message-ID: 20120703150837.34989630@thor
Content-Type: text/plain; charset=US-ASCII

Hi again,

currently I'm trying to figure out how to properly write a parser in
haskell. I've been following the instructions in a book called
Programming in Haskell by Graham Hutton. So far I've written the
following: 



--

Message: 2
Date: Tue, 3 Jul 2012 15:16:02 +0200
From: Robert Heum?ller mail...@heum.de
Subject: Re: [Haskell-beginners] Functional Parses
To: beginners@haskell.org
Message-ID: 20120703151602.02384728@thor
Content-Type: text/plain; charset=US-ASCII

I am sorry, I must have hit the wrong hotkey.
My code looks like this:

type Parser a = String - [(a, String)]

result :: a - Parser a
result v = \inp - [(v, inp)]

zero :: Parser a
zero = \inp - []

item :: Parser Char
item = \inp - case inp of
[] - []
(x:xs) - [(x, xs)]

parse :: Parser a - String - [(a, String)]
parse p inp = p inp

(=) :: Parser a - (a - Parser b) - Parser b
(=) p f = \inp - concat [f v inp' | (v, inp') - p inp]

sat :: (Char - Bool) - Parser Char
sat p = do  x - item
if p x then result x else zero


I beleive I understand how this code is meant to work, but when I run
it in ghci I get the follwing error-message:

parser.hs:21:13:
No instance for (Monad ((-) String))
  arising from a do statement
Possible fix: add an instance declaration for (Monad ((-) String))
In a stmt of a 'do' block: x - item
In the expression:
  do { x - item;
   if p x then result x else zero }
In an equation for `sat':
sat p
  = do { x - item;
 if p x then result x else zero }

parser.hs:22:18:
Couldn't match expected type `Char'
with actual type `[(Char, String)]'
In the first argument of `p', namely `x'
In the expression: p x
In a stmt of a 'do' block: if p x then result x else zero
Failed, modules loaded: none.


Sadly I have no idea how to fix this :( 

Thanks again :)



--

Message: 3
Date: Tue, 03 Jul 2012 16:13:50 +0200
From: Christian Maeder christian.mae...@dfki.de
Subject: Re: [Haskell-beginners] Functional Parses
To: Robert Heum?ller mail...@heum.de
Cc: beginners@haskell.org
Message-ID: 4ff2fe1e.1040...@dfki.de
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Am 03.07.2012 15:16, schrieb Robert Heum?ller:
 I am sorry, I must have hit the wrong hotkey.
 My code looks like this:

 type Parser a = String - [(a, String)]

This type synonym is unsuitable for a Monad instance.
Better would be:
   newtype Parser a = Parser (String - [(a, String)])
but that would require to change your code below.


 result :: a - Parser a
 result v = \inp - [(v, inp)]

 zero :: Parser a
 zero = \inp - []

 item :: Parser Char
 item = \inp - case inp of
  [] - []
  (x:xs) - [(x, xs)]

 parse :: Parser a - String - [(a, String)]
 parse p inp = p inp

 (=) :: Parser a - (a - Parser b) - Parser b
 (=) p f = \inp - concat [f v inp' | (v, inp') - p inp]

Such a definition (without signature and adapted to the newtype) should 
be used within a Monad instance. instance Monad Parser where ...

 sat :: (Char - Bool) - Parser Char
 sat p = do  x - item
  if p x then result x else zero

Without proper Monad instance you should not use do. Instead you could 
expand it yourself manually to:

  sat p = item Main.= \x -
 if p x then result x else zero

Note the clash between your = function (Main.=) and the one from 
the Prelude!

HTH Christian

P.S. there is a instance Monad ((-) r)) in Control.Monad.Instances
but that does not fit your parser type, too.



 I beleive I understand how this code is meant to work, but when I run
 it in ghci I get the follwing error-message:

 parser.hs:21:13:
  No instance for (Monad 

Beginners Digest, Vol 49, Issue 5

2012-07-03 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  Problems with installing lambdabot (Brandon Allbery)
   2. Re:  Functional Parses (Robert Heum?ller)
   3. Re:  Functional Parses (Brandon Allbery)
   4. Re:  Problems with installing lambdabot (Antoras)
   5. Re:  Problems with installing lambdabot (Brent Yorgey)
   6. Re:  Problems with installing lambdabot (Brent Yorgey)


--

Message: 1
Date: Tue, 3 Jul 2012 15:47:30 -0400
From: Brandon Allbery allber...@gmail.com
Subject: Re: [Haskell-beginners] Problems with installing lambdabot
To: Antoras m...@antoras.de
Cc: beginners@haskell.org
Message-ID:
CAKFCL4UD8D10S2SHrv+nDBiW0=9-f7K97d4g6cSb-=9kch5...@mail.gmail.com
Content-Type: text/plain; charset=utf-8

On Tue, Jul 3, 2012 at 3:16 PM, Antoras m...@antoras.de wrote:

 Loading package readline-1.0.1.0 ... command line: can't load .so/.DLL
 for: 
 /usr/lib/gcc/x86_64-unknown-**linux-gnu/4.7.1/../../../../**lib/libncurses.so
 (-lncursesw: cannot open shared object file: No such file or directory)


Your Linux distribution pulled a cute stunt that throws the dynamic loader
(used for TH and ghci and a few other things) for a loop:  libncurses.so,
for backward compatibility purposes, is a GNU ld linker script which
references libncursesw.so in a way the dynamic loader doesn't understand.
 You can work around this in one of two ways:

1. replace /usr/lib/libncurses.so with a symlink to
/usr/lib/libncursesw.so; OR
2. edit /usr/lib/libncurses.so, which is a text file (linker script), to
reference /usr/lib/libncursesw.so instead of -lncursesw.

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120703/9d8c9339/attachment-0001.htm

--

Message: 2
Date: Tue, 3 Jul 2012 23:02:21 +0200
From: Robert Heum?ller mail...@heum.de
Subject: Re: [Haskell-beginners] Functional Parses
To: beginners@haskell.org
Message-ID: 20120703230221.4df7aeff@thor
Content-Type: text/plain; charset=US-ASCII

Thank you very much. 

I'll check out the code on the website tomorrow and hopefully this will
solve the problem. 

Whenever monads apper things seem to get tricky - sadly there won't be
a lecture on functional programming in the next semester at the
university I study at :(


Am Tue, 3 Jul 2012 18:01:32 +0100
schrieb Stephen Tetley stephen.tet...@gmail.com:

 On 3 July 2012 15:13, Christian Maeder christian.mae...@dfki.de
 wrote:
 
  This type synonym is unsuitable for a Monad instance.
  Better would be:
newtype Parser a = Parser (String - [(a, String)])
  but that would require to change your code below.
 
 This is alluded to in the closing chapter remarks (section 8.9) of
 Graham Hutton's book and there is code available on the website that
 accompanies the book that solves the problem. Unfortunately, this
 chapter does seem to trip people up who use the book for self study.
 
 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners




--

Message: 3
Date: Tue, 3 Jul 2012 17:09:20 -0400
From: Brandon Allbery allber...@gmail.com
Subject: Re: [Haskell-beginners] Functional Parses
To: Robert Heum?ller mail...@heum.de
Cc: beginners@haskell.org
Message-ID:
cakfcl4uz0huk4sq+j8xecc6tvcpqntg_hxmwgxifkueo06r...@mail.gmail.com
Content-Type: text/plain; charset=utf-8

On Tue, Jul 3, 2012 at 5:02 PM, Robert Heum?ller mail...@heum.de wrote:

 Whenever monads apper things seem to get tricky - sadly there won't be
 a lecture on functional programming in the next semester at the
 university I study at :(


The only trick here is that the text wants to introduce you to monads by
doing something that won't work in a normal Haskell; you need to put the
compiler in a mode which allows you to in effect rebuild them from scratch.
 (You can't simply provide your own definitions because do notation is
hardwired to use the standard ones anyway, unless you use the
RebindableSyntax extension to tell it to use yours.  You'd also have to
make sure you don't get the standard definitions, which means
NoImplicitPrelude and manually importing Prelude minus the standard
machinery.  I don't think RebindableSyntax let you rebind do notation
properly 

Beginners Digest, Vol 49, Issue 6

2012-07-04 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  What's this [f| data |]  ?? (Carlos J. G. Duarte)
   2. Re:  What's this [f| data |]  ?? (Jack Henahan)
   3. Re:  What's this [f| data |] ?? (David McBride)
   4. Re:  What's this [f| data |]  ?? (Brent Yorgey)
   5. Re:  What's this [f| data |] ?? (Felipe Almeida Lessa)
   6. Re:  What's this [f| data |] ?? (Felipe Almeida Lessa)
   7. Re:  Using tls-extra for simple smtp (Henk-Jan van Tuyl)


--

Message: 1
Date: Wed, 04 Jul 2012 03:10:59 +0100
From: Carlos J. G. Duarte carlos.j.g.dua...@gmail.com
Subject: [Haskell-beginners] What's this [f| data |]  ??
To: beginners@haskell.org
Message-ID: 4ff3a633.8020...@gmail.com
Content-Type: text/plain; charset=iso-8859-1; Format=flowed

Hi. I'm trying to get into haskell in my free time. I have already 
covered some syntax, but there's plenty to do yet, and when I'm 
consulting other people's stuff, I find lots of unknown constructs to 
me, which turns harder to lookup for, due to the very symbolic nature 
of Haskell.

For instance, on this http://www.yesodweb.com/blog/2012/04/yesod-js-todo 
they have a few constructs like this:

|mkYesod  App  [parseRoutes|
/HomeR  GET
/todoTodosR  GET  PUT
/todo/#TodoId  TodoR  GET  DELETE
|]|


It seems that the inline text is going to be fed to parseRoutes. How 
does that constructs work (links?)? I already know list comprehensions 
which appear to be related with this.

Thanks.
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120704/dcef6919/attachment-0001.htm

--

Message: 2
Date: Tue, 3 Jul 2012 22:30:58 -0400
From: Jack Henahan jhena...@uvm.edu
Subject: Re: [Haskell-beginners] What's this [f| data |]  ??
To: Carlos J. G. Duarte carlos.j.g.dua...@gmail.com
Cc: beginners@haskell.org
Message-ID: db99b310-c54e-4362-8d3b-65a7e333e...@uvm.edu
Content-Type: text/plain; charset=iso-8859-1

parseRoutes is a quasiquoter [1]. It uses a type-safe metaprogramming language 
called Template Haskell [2] to parse a string as a Route (e.g., HomeR is a 
Route describing the base resource). You can see the source here [3]. I'm 
pretty new with Yesod, myself, so I'm sure someone else will give you a more in 
depth description shortly.

[1]: http://www.haskell.org/haskellwiki/Quasiquotation
[2]: http://www.haskell.org/haskellwiki/Template_Haskell
[3]: 
http://hackage.haskell.org/packages/archive/yesod-routes/1.0.1.2/doc/html/src/Yesod-Routes-Parse.html#parseRoutes

On Jul 3, 2012, at 10:10 PM, Carlos J. G. Duarte wrote:

 Hi. I'm trying to get into haskell in my free time. I have already covered 
 some syntax, but there's plenty to do yet, and when I'm consulting other 
 people's stuff, I find lots of unknown constructs to me, which turns harder 
 to lookup for, due to the very symbolic nature of Haskell.
 
 For instance, on this http://www.yesodweb.com/blog/2012/04/yesod-js-todo they 
 have a few constructs like this:
 
 mkYesod App
  [parseRoutes|
 / 
 HomeR GET
 
 /todo 
 TodosR GET PUT
 
 /todo/#
 TodoId TodoR GET DELETE
 
 |]
 
 
 It seems that the inline text is going to be fed to parseRoutes. How does 
 that constructs work (links?)? I already know list comprehensions which 
 appear to be related with this. 
 
 Thanks.
 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners

-- next part --
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 841 bytes
Desc: Message signed with OpenPGP using GPGMail
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120703/3f3913a6/attachment-0001.pgp

--

Message: 3
Date: Tue, 3 Jul 2012 22:32:28 -0400
From: David McBride toa...@gmail.com
Subject: Re: [Haskell-beginners] What's this [f| data |] ??
To: Carlos J. G. Duarte carlos.j.g.dua...@gmail.com
Cc: beginners@haskell.org
Message-ID:
CAN+Tr40i2kX371kKcH0Gb30Afw8-fne=4MK+kNy1c7Jj6z+=c...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

This is quasiquoting.  It is a pretty advanced topic, but it allows
you to take an arbitrary string and parse it with a quasiquoter of
your choice (in this case, parseRoutes) into some structure or
another.  Yesod uses it all over the place to generate html,
javascript, routing tables, and such.

On Tue, Jul 3, 2012 at 10:10 

Beginners Digest, Vol 49, Issue 7

2012-07-06 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  Comments on Map/Reduce Code (Thomas Bach)
   2.  arbitrary rank polymorphism and ghc language pragmas (rickmurphy)
   3. Re:  [Haskell-cafe] arbitrary rank polymorphism and ghc
  language pragmas (rickmurphy)
   4.  Expert systems using Haskell (Ramesh Kumar)


--

Message: 1
Date: Thu, 5 Jul 2012 15:50:32 +0200
From: Thomas Bach thb...@students.uni-mainz.de
Subject: [Haskell-beginners] Comments on Map/Reduce Code
To: beginners@haskell.org
Message-ID: 87ipe2mi53@roku.box
Content-Type: text/plain; charset=utf-8

Hello there,

I'm new to Haskell and want to learn it a bit while experimenting with
Hadoop's Map/Reduce programming model. So, I wanted to implement the
standard ?word counter? problem in Haskell. The problem is as follows:

We have several texts with words separated by white-space. We want to
count the occurrences of all words in all the texts (where ?but? and
?but,? can be seen as two different words). This is done in two
phases. In the Map phase a program gets a part of the text from stdout
and has to produce a KEY\tVALUE pair (that is, the key separated with
a tab to the value), which has to be passed to stdin. In our case we
simply produce WordX\t1 for every word WordX. This list is sorted by
the key and later on fed as stdin to the reducer (the second phase). The
reducer now has to sum up all the occurrences we trivially counted in
the Map phase and put it as WordX\tNumber to stdout.

So, here is an example:
vince@roku:~/tmp echo foo foo bar bar foo bar zoo bar foo | runhaskell 
mapper.hs 
foo 1   
  
foo 1
bar 1
bar 1
foo 1
bar 1
zoo 1
bar 1
foo 1
vince@roku:~/tmp echo foo foo bar bar foo bar zoo bar foo | runhaskell 
mapper.hs | sort | runhaskell reducer.hs
bar 4
foo 4
zoo 1

And here is the code I've come up with:

vince@roku:~/tmp cat mapper.hs
import qualified Data.ByteString.Lazy.Char8 as C

postFix :: C.ByteString
postFix = C.pack \t1

formatter :: C.ByteString - C.ByteString
formatter x = C.append x postFix

main :: IO ()
main = do
  contents - fmap C.words C.getContents
  C.putStr . C.unlines $ map formatter contents


vince@roku:~/tmp cat reducer.hs
import qualified Data.ByteString.Lazy.Char8 as C
import qualified Data.List as L

tuppleize :: String - (String, Int)
tuppleize line = (\xs - (head xs, read (last xs))) $ words line

group :: Eq a = [(a, b)] - [[(a, b)]]
group = L.groupBy (\x y - fst x == fst y)

summation :: Num b = [(a, b)] - (a, b)
summation (x:[]) = x
summation (x:xs) = (fst x, (snd x) + (snd (summation xs)))

formatter :: (String, Int) - String
formatter = (\w - (fst w ++ \t ++ show (snd w)))

main = do
  contents - C.getContents
  putStr . unlines $ map formatter $ map summation $ group $ map tuppleize $ 
lines $ C.unpack contents

As already said, I'm a Haskell beginner. Could you provide some comments
on the code?

Thanks in advance,

   Thomas.



--

Message: 2
Date: Thu, 05 Jul 2012 11:18:00 -0400
From: rickmurphy r...@rickmurphy.org
Subject: [Haskell-beginners] arbitrary rank polymorphism and ghc
languagepragmas
To: beginners beginners@haskell.org, haskell-c...@haskell.org
Message-ID: 1341501480.13998.36.camel@metho-laptop
Content-Type: text/plain; charset=UTF-8

Hi All:

I've been working through some details in these papers [1], [2] and
noticed a language pragma configuration that I hope you can confirm.

When using explicit foralls in a data constructor, it appears that GHC
7.4.2 requires Rank2Types in the Language pragma for what the papers
consider rank 1 types. 

Here's an example:

data T = TC (forall a b. a - b - a)

Am I correct, or is there another extension? The ExplicitForAll does not
appear to support rank 1 types in data constructors.

1. Practical Type Inference for Arbitrary-Rank Types.
2. A Direct Algorithm for Type Inference in the Rank 2 Fragment of the
Second-Order Lambda Calculus.

--
Rick




--

Message: 3
Date: Thu, 05 Jul 2012 13:17:12 -0400
From: rickmurphy r...@rickmurphy.org
Subject: Re: [Haskell-beginners] [Haskell-cafe] arbitrary rank
polymorphism and ghc language pragmas
To: beginners beginners@haskell.org, haskell-c...@haskell.org
Message-ID: 1341508632.14924.3.camel@metho-laptop
Content-Type: text/plain; charset=UTF-8

Thanks Francesco. And I did verify 

Beginners Digest, Vol 49, Issue 11

2012-07-11 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  Comments on Map/Reduce Code (Brent Yorgey)
   2.  Trouble compiling haskell platfrom (Jeff Lasslett)


--

Message: 1
Date: Tue, 10 Jul 2012 10:19:48 -0400
From: Brent Yorgey byor...@seas.upenn.edu
Subject: Re: [Haskell-beginners] Comments on Map/Reduce Code
To: beginners@haskell.org
Message-ID: 20120710141948.ga16...@seas.upenn.edu
Content-Type: text/plain; charset=us-ascii

On Thu, Jul 05, 2012 at 03:50:32PM +0200, Thomas Bach wrote:
 Hello there,

Hi Thomas,

Looks pretty good.  I've interspersed a few comments below.


 And here is the code I've come up with:
 
 vince@roku:~/tmp cat mapper.hs
 import qualified Data.ByteString.Lazy.Char8 as C
 
 postFix :: C.ByteString
 postFix = C.pack \t1
 
 formatter :: C.ByteString - C.ByteString
 formatter x = C.append x postFix
 
 main :: IO ()
 main = do
   contents - fmap C.words C.getContents
   C.putStr . C.unlines $ map formatter contents

The above looks fine, except that generally the recommendation is to
use the text package [1] for dealing with text, whereas ByteString is
for binary data that you wish to manipulate as a sequence of bytes.
You can get away with the above only when the text consists entirely
of ASCII characters.

[1] http://hackage.haskell.org/package/text

 vince@roku:~/tmp cat reducer.hs
 import qualified Data.ByteString.Lazy.Char8 as C
 import qualified Data.List as L
 
 tuppleize :: String - (String, Int)
 tuppleize line = (\xs - (head xs, read (last xs))) $ words line

What happens when the line is empty?

 group :: Eq a = [(a, b)] - [[(a, b)]]
 group = L.groupBy (\x y - fst x == fst y)

The above lambda can also be written as ((==) `on` fst).  'on' can be
imported from Data.Function.

 
 summation :: Num b = [(a, b)] - (a, b)
 summation (x:[]) = x
 summation (x:xs) = (fst x, (snd x) + (snd (summation xs)))

Instead of using (fst x) and (snd x), you should pattern-match on x,
like

  summation ((x,y):xs) = (x, y + ...)

 formatter :: (String, Int) - String
 formatter = (\w - (fst w ++ \t ++ show (snd w)))

The same goes here.  I would also put the w argument on the left-hand
side of the =, like

  formatter (s,i) = s ++ \t ++ show i

 
 main = do
   contents - C.getContents
   putStr . unlines $ map formatter $ map summation $ group $ map tuppleize $ 
 lines $ C.unpack contents

Instead of using a chain of ($), it's generally considered better
style to use a chain of (.) with a single $ at the end, like

  putStr . unlines . map formatter ... lines . C.unpack $ contents

-Brent



--

Message: 2
Date: Wed, 11 Jul 2012 10:07:38 +1000
From: Jeff Lasslett jeff.lassl...@gmail.com
Subject: [Haskell-beginners] Trouble compiling haskell platfrom
To: Beginners@haskell.org
Message-ID:
CAK6+hbxU5k=p0-3myvxf6j5xvao9lta7fkrg2kotvv6wtrp...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

Greetings,

I'm trying to recompile  reinstall the haskell platform 12.2.0.0.  I
have installed it successfully on a prior occasion  but I decided to
reinstall as I think I may have messed up my installed packages a bit
while playing around with yesod.   I intend to use cabal-dev or
virtualenv for that in future.

So I thought I'd do a clean install.  I blew away my haskell platform
and ghc, both of which were installed in a dir under my home dir.  I
also blew away my ~/.cabal/ dir.

I then reinstalled by ghc 7.4.1 into ~/prg/haskell-platform-12.2.0.0.

I then unpacked the sources of haskell-platform-12.2.0.0 and
configured it with the prefix set to where ghc is.

configure finished without error so I ran 'make'.  It quits with what
follows.  How do I fix this??

With thanks,

Jeff



* Now do make followed by make install
**
jeff@chunks:~/src/haskell-platform-2012.2.0.0$ make
scripts/build.sh
**
Scanning system for any installed Haskell Platform components...

Found: HUnit-1.2.4.2 OpenGL-2.2.3.1 GLUT-2.1.2.1 html-1.0.1.2
parallel-3.2.0.2 random-1.0.1.1 QuickCheck-2.4.2 stm-2.3 syb-0.3.6.1
haskell-src-1.0.1.5 text-0.11.2.0 transformers-0.3.0.0 mtl-2.1.1
fgl-5.4.2.4 parsec-3.1.2 network-2.3.0.13 HTTP-4000.2.3
regex-base-0.93.2 regex-posix-0.95.1 regex-compat-0.95.1
xhtml-3000.2.1 cgi-3001.1.7.4 zlib-0.5.3.3 haskell-platform-2012.2.0.0

New packages to install: None! All done.

**
Building alex-3.0.1

Beginners Digest, Vol 49, Issue 12

2012-07-12 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  Trouble compiling haskell platfrom (gdwe...@iue.edu)
   2. Re:  Trouble compiling haskell platfrom (Jeff Lasslett)
   3. Re:  Concurrent vs GHC (Mauricio Hernandes)
   4.  Hackage down? (Lorenzo Bolla)


--

Message: 1
Date: Wed, 11 Jul 2012 16:48:13 -0400
From: gdwe...@iue.edu
Subject: Re: [Haskell-beginners] Trouble compiling haskell platfrom
To: Jeff Lasslett jeff.lassl...@gmail.com
Cc: Beginners@haskell.org
Message-ID: 20120711204813.gg...@tramp.ftrdhcpuser.net
Content-Type: text/plain; charset=us-ascii

Hi,

On 2012-Jul-11, Jeff Lasslett wrote:
 Greetings,
 
 I'm trying to recompile  reinstall the haskell platform 12.2.0.0.  I
 have installed it successfully on a prior occasion  but I decided to
 reinstall as I think I may have messed up my installed packages a bit
 while playing around with yesod.   I intend to use cabal-dev or
 virtualenv for that in future.
 
 So I thought I'd do a clean install.  I blew away my haskell platform
 and ghc, both of which were installed in a dir under my home dir.  I
 also blew away my ~/.cabal/ dir.
 
 I then reinstalled by ghc 7.4.1 into ~/prg/haskell-platform-12.2.0.0.
 
 I then unpacked the sources of haskell-platform-12.2.0.0 and
 configured it with the prefix set to where ghc is.
 
 configure finished without error so I ran 'make'.  It quits with what
 follows.  How do I fix this??
 
 With thanks,
 
 Jeff
 
 
 
 * Now do make followed by make install
 **
 jeff@chunks:~/src/haskell-platform-2012.2.0.0$ make
 scripts/build.sh
 **
 Scanning system for any installed Haskell Platform components...
 
 Found: HUnit-1.2.4.2 OpenGL-2.2.3.1 GLUT-2.1.2.1 html-1.0.1.2
 parallel-3.2.0.2 random-1.0.1.1 QuickCheck-2.4.2 stm-2.3 syb-0.3.6.1
 haskell-src-1.0.1.5 text-0.11.2.0 transformers-0.3.0.0 mtl-2.1.1
 fgl-5.4.2.4 parsec-3.1.2 network-2.3.0.13 HTTP-4000.2.3
 regex-base-0.93.2 regex-posix-0.95.1 regex-compat-0.95.1
 xhtml-3000.2.1 cgi-3001.1.7.4 zlib-0.5.3.3 haskell-platform-2012.2.0.0
 
 New packages to install: None! All done.
 
 **
 Building alex-3.0.1
 /home/jeff/prg/haskell-platform-12.2.0.0/bin/ghc --make Setup
 -o Setup -package Cabal-1.14.0
 Linking Setup ...
 ./Setup configure
 --package-db=../../packages/package.conf.inplace
 --prefix=/home/jeff/prg/haskell-platform-12.2.0.0
 --with-compiler=/home/jeff/prg/haskell-platform-12.2.0.0/bin/ghc
 --with-hc-pkg=/home/jeff/prg/haskell-platform-12.2.0.0/bin/ghc-pkg
 --with-hsc2hs=/home/jeff/prg/haskell-platform-12.2.0.0/bin/hsc2hs
 --enable-library-profiling
 --ghc-pkg-option=--package-conf=../../packages/package.conf.inplace
 --user
 Warning: defaultUserHooks in Setup script is deprecated.
 Configuring alex-3.0.1...
 ./Setup build
 Building alex-3.0.1...
 Preprocessing executable 'alex' for alex-3.0.1...
 
 src/Data/Ranged/RangedSet.hs:64:8:
 Could not find module `Test.QuickCheck'
 There are files missing in the `QuickCheck-2.4.2' package,
 try running 'ghc-pkg check'.
 Use -v to see a list of the files searched for.

I would suggest start by doing what it says just above: 
run `ghc-pkg check`.

This will give you a list of broken packages.
For each such package `P`, run `ghc-pkg unregister P`.

Then you can try installing Haskell Platform again,
starting with the configure step.

For a detailed explanation of what's going on here,
see Albert Lai's Storage and Identification of Cabalized Packages:

http://www.vex.net/~trebla/haskell/sicp.xhtml


 
 Error:
 Building the alex-3.0.1 package failed
 make: *** [build.stamp] Error 2
 
 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners

-- 
Gregory D. Weber, Ph. D.:
Associate Professor of Informatics / \
Indiana University East   0   :
Tel. (765) 973-8420; FAX (765) 973-8550  / \
http://mypage.iu.edu/~gdweber/  1  []



--

Message: 2
Date: Thu, 12 Jul 2012 14:01:12 +1000
From: Jeff Lasslett jeff.lassl...@gmail.com
Subject: Re: [Haskell-beginners] Trouble compiling haskell platfrom
To: gdwe...@iue.edu
Cc: Beginners@haskell.org
Message-ID:
cak6+hby1quu6ssf8u2oh_pnyb3dcbvl65m5r++3krm6c1tn...@mail.gmail.com
Content-Type: 

Beginners Digest, Vol 49, Issue 13

2012-07-13 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  Hackage down? (Mauricio Hernandes)
   2. Re:  Hackage down? (Brent Yorgey)


--

Message: 1
Date: Thu, 12 Jul 2012 23:51:39 +0900
From: Mauricio Hernandes maukeshig...@gmail.com
Subject: Re: [Haskell-beginners] Hackage down?
To: Lorenzo Bolla lbo...@gmail.com
Cc: beginners@haskell.org
Message-ID:
CAOons7a9k6KGxDpywZwHY7hSb9AZ6qmiZGsC=rcv-auogxj...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

I had the same problem today :(
but I think at least hoogle is working already \o/


On Thu, Jul 12, 2012 at 4:51 PM, Lorenzo Bolla lbo...@gmail.com wrote:

 Is hackage.haskell.org down?
 cabal update times out here...

 How do you guys work around this? It seems to happen pretty often.

 L.

 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners


-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120712/93a06915/attachment-0001.htm

--

Message: 2
Date: Thu, 12 Jul 2012 11:29:42 -0400
From: Brent Yorgey byor...@seas.upenn.edu
Subject: Re: [Haskell-beginners] Hackage down?
To: beginners@haskell.org
Message-ID: 20120712152942.ga9...@seas.upenn.edu
Content-Type: text/plain; charset=us-ascii

Looks like Hackage is back up now.  The official word is that
something (not sure what yet) was hitting the server really hard and
causing the load average to go through the roof, and it had to be
rebooted.

For future reference, an up-to-date mirror of the packages is
maintained at 

  http://hdiff.luite.com/packages/archive/

-Brent

On Thu, Jul 12, 2012 at 08:51:48AM +0100, Lorenzo Bolla wrote:
Is hackage.haskell.org down?
cabal update times out here...
How do you guys work around this? It seems to happen pretty often.
L.

 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners




--

___
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 49, Issue 13
*


Beginners Digest, Vol 49, Issue 16

2012-07-15 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  Review request (C K Kashyap)
   2.  I can see lists working for matrix algorithms if the
  access patterns are mostly from the start or end of rows and
  columns. (KC)
   3.  DPH installation and LLVM (listig...@gmail.com)
   4. Re:  DPH installation and LLVM (Brandon Allbery)
   5. Re:  Review request (Carlos J. G. Duarte)
   6. Re:  DPH installation and LLVM (listig...@gmail.com)


--

Message: 1
Date: Sun, 15 Jul 2012 17:38:29 +0530
From: C K Kashyap ckkash...@gmail.com
Subject: [Haskell-beginners] Review request
To: beginners beginners@haskell.org
Message-ID:
CAGdT1goLUM8TxA=ntyuvmpdyackf5m_c6_jb7fmu5-zmerw...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

Hi,
I've written a small haskell program to extract a section from a file
between start and end markers. For example, if I have a file such as below
-
a
b
c
bug
d
e
f
/bug
g
h
i

I'd like to extract the contents between bug and /bug (including the
markers).

startTag = bugendTag = /bug
process  = unlines . specialTakeWhile (f endTag) . dropWhile (f
startTag) . lines
where f t x = not (x =~ t)
  specialTakeWhile :: (a - Bool) - [a] - [a]
  specialTakeWhile ff [] = []
  specialTakeWhile ff (x:xs) = if ff x then
x:(specialTakeWhile ff xs) else [x]



It'll be great if I could get some feedback on this.


Regards,

Kashyap
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120715/77950c5b/attachment-0001.htm

--

Message: 2
Date: Sun, 15 Jul 2012 11:01:40 -0700
From: KC kc1...@gmail.com
Subject: [Haskell-beginners] I can see lists working for matrix
algorithms if the access patterns are mostly from the start or end of
rows and columns.
To: haskell-cafe haskell-c...@haskell.org, beginners@haskell.org
Message-ID:
CAMLKXynLpMEEh8ZEZe0c07WSJP=jbwwbxesuoqf2bc2pdbv...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

Are there any such matrix algorithms that operate mainly from the start or
end or rows and columns?

Note: If the access pattern starts from the end of a row then one stores
the row in reverse order in a list.

-- 
--
Regards,
KC
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120715/bd9c364a/attachment-0001.htm

--

Message: 3
Date: Sun, 15 Jul 2012 14:49:47 -0400
From: listig...@gmail.com
Subject: [Haskell-beginners] DPH installation and LLVM
To: beginners@haskell.org
Message-ID: c418f1b4-4131-43a1-8799-492884b13...@gmail.com
Content-Type: text/plain; charset=us-ascii

Dear all,

being completely new to Haskell I wanted to explore what DPH is about, so I 
tried to install it via

cabal install dph-examples

but the installation process stops once it gets to installing the actual 
examples package:

---
Building dph-examples-0.6.1.3...
Preprocessing executable 'dph-spectral-smvm' for dph-examples-0.6.1.3...
[1 of 3] Compiling Vectorised   ( examples/spectral/SMVM/dph/Vectorised.hs, 
dist/build/dph-spectral-smvm/dph-spectral-smvm-tmp/Vectorised.o )
exprType TYPE ghc-prim:GHC.Types.Double{(w) tc 3u}
exprType TYPE ghc-prim:GHC.Types.Double{(w) tc 3u}
exprType TYPE ghc-prim:GHC.Types.Double{(w) tc 3u}
exprType TYPE ghc-prim:GHC.Types.Double{(w) tc 3u}
exprType TYPE ghc-prim:GHC.Types.Double{(w) tc 3u}
exprType
TYPE (ghc-prim:GHC.Types.Int{(w) tc 3J},
  ghc-prim:GHC.Types.Double{(w) tc 3u})
Warning: Couldn't figure out LLVM version!
 Make sure you have installed LLVM
ghc: could not execute: opt
cabal: Error: some packages failed to install:
dph-examples-0.6.1.3 failed during the building phase. The exception was:
ExitFailure 1
---

This is the rest of my setup:

Mac OS X 10.7.4
Xcode 4.3.3 + Command Line Tools (from within Xcode)
Haskell Platform 2012.2.0.0 32bit

Why doesn't Haskell find the LLVM compiler? Is there a way to install the 
remaining examples without LLVM compilation?

Thanks,
Oliver


--

Message: 4
Date: Sun, 15 Jul 2012 14:56:32 -0400
From: Brandon Allbery allber...@gmail.com
Subject: Re: [Haskell-beginners] DPH installation and LLVM
To: listig...@gmail.com
Cc: beginners@haskell.org
Message-ID:

Beginners Digest, Vol 49, Issue 18

2012-07-17 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  Review request (C K Kashyap)
   2. Re:  Review request (Carlos J. G. Duarte)


--

Message: 1
Date: Mon, 16 Jul 2012 16:40:45 +0530
From: C K Kashyap ckkash...@gmail.com
Subject: Re: [Haskell-beginners] Review request
To: Carlos J. G. Duarte carlos.j.g.dua...@gmail.com
Cc: beginners@haskell.org
Message-ID:
cagdt1govmw+mimmmq-xcejzdwcx1uzrf+w11pdmuembafsa...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

Thanks Carlos - you can import Text.Regex.Posix to get (=~)
Is there a way to avoid the (++) in your implementation? It has a linear
time overhead.

Regards,
Kashyap

On Mon, Jul 16, 2012 at 1:36 AM, Carlos J. G. Duarte 
carlos.j.g.dua...@gmail.com wrote:

  Looks good to me, but I'm just a beginner!
 I used the isInfixOf from Data.List instead of =~ to run your example
 because the later wasn't working on my instalation.

 I've made a slightly variant using the break function:

 import Data.List

 startTag = bug
 endTag = /bug

 main = interact process

 process  = unlines . extractSection startTag endTag . lines
 extractSection start stop xs =
   let (ls,rs) = break (isInfixOf stop) $ dropWhile (not . isInfixOf start)
 xs
   in ls ++ take 1 rs



 On 07/15/12 13:08, C K Kashyap wrote:

 Hi,
 I've written a small haskell program to extract a section from a file
 between start and end markers. For example, if I have a file such as below
 -
  a
 b
 c
 bug
 d
 e
 f
 /bug
 g
 h
 i

  I'd like to extract the contents between bug and /bug (including the
 markers).

  startTag = bugendTag = /bug
 process  = unlines . specialTakeWhile (f endTag) . dropWhile (f startTag) . 
 lines
 where f t x = not (x =~ t)
   specialTakeWhile :: (a - Bool) - [a] - [a]
   specialTakeWhile ff [] = []
   specialTakeWhile ff (x:xs) = if ff x then x:(specialTakeWhile 
 ff xs)** else [x]

   It'll be great if I could get some feedback on this.

  Regards,

 Kashyap



 ___
 Beginners mailing 
 listBeginners@haskell.orghttp://www.haskell.org/mailman/listinfo/beginners




 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners


-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120716/491783ee/attachment-0001.htm

--

Message: 2
Date: Mon, 16 Jul 2012 17:57:59 +0100
From: Carlos J. G. Duarte carlos.j.g.dua...@gmail.com
Subject: Re: [Haskell-beginners] Review request
To: beginners@haskell.org
Message-ID: 50044817.1000...@gmail.com
Content-Type: text/plain; charset=us-ascii

An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120716/7a39c0a5/attachment-0001.htm

--

___
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 49, Issue 18
*


Beginners Digest, Vol 49, Issue 20

2012-07-18 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  How do I marshall a pointer over SendMessage LPARAM or
  WPARAM? (Simon Peter Nicholls)
   2. Re:  How do I marshall a pointer over SendMessage LPARAM or
  WPARAM? (Brent Yorgey)
   3. Re:  How do I marshall a pointer over SendMessage LPARAM or
  WPARAM? (Sylvain HENRY)
   4. Re:  How do I marshall a pointer over SendMessage LPARAM or
  WPARAM? (Simon Peter Nicholls)
   5. Re:  How do I marshall a pointer over SendMessage LPARAM or
  WPARAM? (Sylvain HENRY)
   6. Re:  How do I marshall a pointer over SendMessage LPARAM or
  WPARAM? (Simon Peter Nicholls)


--

Message: 1
Date: Wed, 18 Jul 2012 15:14:46 +0200
From: Simon Peter Nicholls si...@mintsource.org
Subject: [Haskell-beginners] How do I marshall a pointer over
SendMessage LPARAM or WPARAM?
To: beginners@haskell.org
Message-ID:
caeacojkqwr69jueswg5te4fq1p2nszo2cqrtdqbbyevye7p...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

I'm new to Haskell, and have had some good success with FFI so far,
but using Win32's sendMessage to send a pointer in LPARAM or WPARAM is
resulting in access violations at the other end.

Is there some issue with my pointer conversions? Am I hitting some
restriction, or missing some compiler options?


 It's driving me pretty crazy, after a very nice start to using Haskell.

Some sending code:

Foreign.C.String.withCWString frustrator $ \s - do
let wParam = System.Win32.Types.castPtrToUINT s ::
System.Win32.Types.WPARAM
Graphics.Win32.sendMessage wnd Graphics.Win32.wM_APP wParam 0

wndProc receiving code:

| wmsg == Graphics.Win32.wM_APP = do
s - peekCWString $ System.Win32.Types.castUINTToPtr wParam
putStrLn s
return 0

The string will not be seen.

Some extra notes:

I can get wndProc messages and integral data generally.
The pointer values match textually at both ends when shown to stdout.
At the sending side I can pass the CWString to a regular FFI function
call just fine, and castUINTToPtr will give me back a functioning Ptr
for that call.

 I have also tried sending to  receiving from a working C++ program,
without success. Access violations are reported when receiving, though
again the address matches up. Silence from Haskell as before, when C++
is sending.

I found someone else having an issue here:
http://osdir.com/ml/haskell-c...@haskell.org/2009-11/msg00731.html but
no solution unfortunately.



--

Message: 2
Date: Wed, 18 Jul 2012 11:47:40 -0400
From: Brent Yorgey byor...@seas.upenn.edu
Subject: Re: [Haskell-beginners] How do I marshall a pointer over
SendMessage LPARAM or WPARAM?
To: beginners@haskell.org
Message-ID: 20120718154740.ga27...@seas.upenn.edu
Content-Type: text/plain; charset=us-ascii

Hi,

Just a meta-comment: this doesn't seem like a beginner question to
me. =) Perhaps someone on this list will know the answer (and there's
nothing wrong with asking), but for such a specific question you may
have better luck posting to haskell-cafe or StackOverflow.

-Brent

On Wed, Jul 18, 2012 at 03:14:46PM +0200, Simon Peter Nicholls wrote:
 I'm new to Haskell, and have had some good success with FFI so far,
 but using Win32's sendMessage to send a pointer in LPARAM or WPARAM is
 resulting in access violations at the other end.
 
 Is there some issue with my pointer conversions? Am I hitting some
 restriction, or missing some compiler options?
 
 
  It's driving me pretty crazy, after a very nice start to using Haskell.
 
 Some sending code:
 
 Foreign.C.String.withCWString frustrator $ \s - do
 let wParam = System.Win32.Types.castPtrToUINT s ::
 System.Win32.Types.WPARAM
 Graphics.Win32.sendMessage wnd Graphics.Win32.wM_APP wParam 0
 
 wndProc receiving code:
 
 | wmsg == Graphics.Win32.wM_APP = do
 s - peekCWString $ System.Win32.Types.castUINTToPtr wParam
 putStrLn s
 return 0
 
 The string will not be seen.
 
 Some extra notes:
 
 I can get wndProc messages and integral data generally.
 The pointer values match textually at both ends when shown to stdout.
 At the sending side I can pass the CWString to a regular FFI function
 call just fine, and castUINTToPtr will give me back a functioning Ptr
 for that call.
 
  I have also tried sending to  receiving from a working C++ program,
 without success. Access 

Beginners Digest, Vol 49, Issue 21

2012-07-18 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  How do I marshall a pointer over SendMessage LPARAM or
  WPARAM? (Sylvain HENRY)
   2. Re:  How do I marshall a pointer over SendMessage LPARAM or
  WPARAM? (Simon Peter Nicholls)
   3. Re:  How do I marshall a pointer over SendMessage LPARAM or
  WPARAM? (Simon Peter Nicholls)
   4. Re:  haskell for system administration (Erik Johnson)


--

Message: 1
Date: Wed, 18 Jul 2012 19:13:00 +0200
From: Sylvain HENRY hsy...@gmail.com
Subject: Re: [Haskell-beginners] How do I marshall a pointer over
SendMessage LPARAM or WPARAM?
To: beginners@haskell.org
Message-ID: 5006ee9c.5060...@gmail.com
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

If you are doing inter-process communication, you should not send 
pointers as processes do not share the same address space.

Use WM_COPYDATA to send a specific amount of data. 
http://msdn.microsoft.com/en-us/library/windows/desktop/ms649011%28v=vs.85%29.aspx

I've read that SendMessage is blocking, so you can use withCWString 
(contrary to what I have previously written). As you have to pass the 
size of the data, you can even use withCWStringLen (and peekCWStringLen).

Cheers
Sylvain

Le 18/07/2012 19:02, Simon Peter Nicholls a ?crit :
 It's inter-process by design.

 I have a small single instance  C++ program that I'm porting to
 Haskell. Once the first instance launched is up and running,
 subsequent launches send their command line params through to the
 single instance (file names). Similar to when a media player queues
 files in a play list.

 The most recent extra clue I have is that if I wrap the SendMessage
 function with my own C FFI version, my C function can both re-cast and
 output the CWString I have sent, and can successfully invoke the real
 SendMessage by overriding the CWString with a newly created Lblah
 string. It's just a shame it can't use the original!

 My next session will involve poking around at the two strings to learn
 why they are treated differently.

 On Wed, Jul 18, 2012 at 6:33 PM, Sylvain HENRY hsy...@gmail.com wrote:
 Are you sending the message to a window of the same process?

 -Sylvain

 Le 18/07/2012 18:28, Simon Peter Nicholls a ?crit :

 I've tried that without joy. Have reposted over at Haskell cafe, as
 per Brent's advice. Thanks to both of you.

 On Wed, Jul 18, 2012 at 5:56 PM, Sylvain HENRY hsy...@gmail.com wrote:
 Hi,

 [As I've just registered to the list, I don't have the original message.
 That's why I answer to Brent insted of Simon]

 By using withCWString, your CWString may be freed before the message is
 sent. Use newCWString instead and free in your receiving code.

 Cheers
 Sylvain

 Le 18/07/2012 17:47, Brent Yorgey a ?crit :

 Hi,

 Just a meta-comment: this doesn't seem like a beginner question to
 me. =) Perhaps someone on this list will know the answer (and there's
 nothing wrong with asking), but for such a specific question you may
 have better luck posting to haskell-cafe or StackOverflow.

 -Brent

 On Wed, Jul 18, 2012 at 03:14:46PM +0200, Simon Peter Nicholls wrote:
 I'm new to Haskell, and have had some good success with FFI so far,
 but using Win32's sendMessage to send a pointer in LPARAM or WPARAM is
 resulting in access violations at the other end.

 Is there some issue with my pointer conversions? Am I hitting some
 restriction, or missing some compiler options?


 It's driving me pretty crazy, after a very nice start to using
 Haskell.

 Some sending code:

Foreign.C.String.withCWString frustrator $ \s - do
let wParam = System.Win32.Types.castPtrToUINT s ::
 System.Win32.Types.WPARAM
Graphics.Win32.sendMessage wnd Graphics.Win32.wM_APP
 wParam 0

 wndProc receiving code:

| wmsg == Graphics.Win32.wM_APP = do
s - peekCWString $ System.Win32.Types.castUINTToPtr wParam
putStrLn s
return 0

 The string will not be seen.

 Some extra notes:

 I can get wndProc messages and integral data generally.
 The pointer values match textually at both ends when shown to stdout.
 At the sending side I can pass the CWString to a regular FFI function
 call just fine, and castUINTToPtr will give me back a functioning Ptr
 for that call.

 I have also tried sending to  receiving from a working C++ program,
 without success. Access violations are reported when receiving, though
 again the address matches up. 

Beginners Digest, Vol 49, Issue 22

2012-07-19 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  How do I marshall a pointer over SendMessage LPARAM or
  WPARAM? (Brent Yorgey)
   2.  Where do you put your tests? (Lorenzo Bolla)


--

Message: 1
Date: Wed, 18 Jul 2012 16:28:09 -0400
From: Brent Yorgey byor...@seas.upenn.edu
Subject: Re: [Haskell-beginners] How do I marshall a pointer over
SendMessage LPARAM or WPARAM?
To: beginners@haskell.org
Message-ID: 20120718202809.ga11...@seas.upenn.edu
Content-Type: text/plain; charset=iso-8859-1

I'm very glad to have been proven wrong about someone on the beginners
list being able to help. =)

On Wed, Jul 18, 2012 at 09:40:51PM +0200, Simon Peter Nicholls wrote:
 Well, I couldn't wait until tomorrow of course.
 
 I just had to have an after-dinner hack, tried again with WM_COPYDATA
 / COPYDATASTRUCT, and it worked first time!
 
 Thanks again for your help!
 
 On Wed, Jul 18, 2012 at 7:13 PM, Sylvain HENRY hsy...@gmail.com wrote:
  If you are doing inter-process communication, you should not send pointers
  as processes do not share the same address space.
 
  Use WM_COPYDATA to send a specific amount of data.
  http://msdn.microsoft.com/en-us/library/windows/desktop/ms649011%28v=vs.85%29.aspx
 
  I've read that SendMessage is blocking, so you can use withCWString
  (contrary to what I have previously written). As you have to pass the size
  of the data, you can even use withCWStringLen (and peekCWStringLen).
 
  Cheers
  Sylvain
 
  Le 18/07/2012 19:02, Simon Peter Nicholls a ?crit :
 
  It's inter-process by design.
 
  I have a small single instance  C++ program that I'm porting to
  Haskell. Once the first instance launched is up and running,
  subsequent launches send their command line params through to the
  single instance (file names). Similar to when a media player queues
  files in a play list.
 
  The most recent extra clue I have is that if I wrap the SendMessage
  function with my own C FFI version, my C function can both re-cast and
  output the CWString I have sent, and can successfully invoke the real
  SendMessage by overriding the CWString with a newly created Lblah
  string. It's just a shame it can't use the original!
 
  My next session will involve poking around at the two strings to learn
  why they are treated differently.
 
  On Wed, Jul 18, 2012 at 6:33 PM, Sylvain HENRY hsy...@gmail.com wrote:
 
  Are you sending the message to a window of the same process?
 
  -Sylvain
 
  Le 18/07/2012 18:28, Simon Peter Nicholls a ?crit :
 
  I've tried that without joy. Have reposted over at Haskell cafe, as
  per Brent's advice. Thanks to both of you.
 
  On Wed, Jul 18, 2012 at 5:56 PM, Sylvain HENRY hsy...@gmail.com wrote:
 
  Hi,
 
  [As I've just registered to the list, I don't have the original
  message.
  That's why I answer to Brent insted of Simon]
 
  By using withCWString, your CWString may be freed before the message
  is
  sent. Use newCWString instead and free in your receiving code.
 
  Cheers
  Sylvain
 
  Le 18/07/2012 17:47, Brent Yorgey a ?crit :
 
  Hi,
 
  Just a meta-comment: this doesn't seem like a beginner question to
  me. =) Perhaps someone on this list will know the answer (and there's
  nothing wrong with asking), but for such a specific question you may
  have better luck posting to haskell-cafe or StackOverflow.
 
  -Brent
 
  On Wed, Jul 18, 2012 at 03:14:46PM +0200, Simon Peter Nicholls wrote:
 
  I'm new to Haskell, and have had some good success with FFI so far,
  but using Win32's sendMessage to send a pointer in LPARAM or WPARAM
  is
  resulting in access violations at the other end.
 
  Is there some issue with my pointer conversions? Am I hitting some
  restriction, or missing some compiler options?
 
 
  It's driving me pretty crazy, after a very nice start to using
  Haskell.
 
  Some sending code:
 
 Foreign.C.String.withCWString frustrator $ \s - do
 let wParam = System.Win32.Types.castPtrToUINT s ::
  System.Win32.Types.WPARAM
 Graphics.Win32.sendMessage wnd
  Graphics.Win32.wM_APP
  wParam 0
 
  wndProc receiving code:
 
 | wmsg == Graphics.Win32.wM_APP = do
 s - peekCWString $ System.Win32.Types.castUINTToPtr
  wParam
 putStrLn s
 return 0
 
  The string will not be seen.
 
  Some extra notes:
 
  I can get wndProc messages and integral data generally.
  The pointer values match textually at both ends when shown 

Beginners Digest, Vol 49, Issue 23

2012-07-20 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  Where do you put your tests? (damodar kulkarni)
   2.  automatically clean up Haskell code? (Christopher Howard)
   3. Re:  automatically clean up Haskell code? (Karol Samborski)


--

Message: 1
Date: Thu, 19 Jul 2012 18:57:10 +0530
From: damodar kulkarni kdamodar2...@gmail.com
Subject: Re: [Haskell-beginners] Where do you put your tests?
To: Lorenzo Bolla lbo...@gmail.com
Cc: beginners@haskell.org
Message-ID:
CAD5HsyoxG8JD9_002nuTUbA=3Q3AOJFE3HTVkF7B4Z_2Q=+d...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

 Good because library dependencies are reduced, but bad because tests are
 somewhat disconnected from the functions they are testing.


AFAIK, it's a good engineering practice to separate the tests from the code
they are supposed to test. Code management issues will be there, but those
can be taken care with the help of cabal like tool.
That way, a person who wants to test will use the test-files and the one
who doesn't want will be spared the trouble of separating tests from the
intended function code.

Regards,
 Damodar


On Thu, Jul 19, 2012 at 1:46 PM, Lorenzo Bolla lbo...@gmail.com wrote:

 Hi all,

 I'm writing some library code and I have hunit-tests and quickcheck-tests.
 I'm facing the problem of where to put these tests. These are the options I
 can think of:

- Put the tests for a function in the same file where the function is
defined. This is good because tests are close to the code being tested and
work as a sort of documentation for it. But it's bad because the file
requires HUnit, QuickCheck, Test.Framework, etc. to compile.
- Same as above, but use some sort of preprocessing flag to ignore the
Test suite when compiling the library (hence no dependencies on test
libraries), but leave the code in place. No dependencies, but ugly.
- Put the tests in completely separate files. Good because library
dependencies are reduced, but bad because tests are somewhat disconnected
from the functions they are testing.

 What do you expert suggest? How should I organize my test suites?
 (The same conundrum applies to benchmarking code.)

 Thanks,
 Lorenzo

 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners


-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120719/4058cde5/attachment-0001.htm

--

Message: 2
Date: Thu, 19 Jul 2012 18:19:36 -0800
From: Christopher Howard christopher.how...@frigidcode.com
Subject: [Haskell-beginners] automatically clean up Haskell code?
To: Haskell Beginners beginners@haskell.org
Message-ID: 5008c038.5000...@frigidcode.com
Content-Type: text/plain; charset=iso-8859-1

Is there a program that can automatically clean up your Haskell code?
That is, shrink to 80 columns, make tidy indentation, remove unnecessary
whitespace, and all that sort of stuff...?

-- 
frigidcode.com
indicium.us

-- next part --
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 554 bytes
Desc: OpenPGP digital signature
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120719/2ec3679a/attachment-0001.pgp

--

Message: 3
Date: Fri, 20 Jul 2012 09:24:09 +0200
From: Karol Samborski edv.ka...@gmail.com
Subject: Re: [Haskell-beginners] automatically clean up Haskell code?
To: Christopher Howard christopher.how...@frigidcode.com
Cc: Haskell Beginners beginners@haskell.org
Message-ID:
cace2dtuges_j94phmjfoa0yda9frht03q27ophogcudatmt...@mail.gmail.com
Content-Type: text/plain; charset=UTF-8

2012/7/20 Christopher Howard christopher.how...@frigidcode.com:
 Is there a program that can automatically clean up your Haskell code?
 That is, shrink to 80 columns, make tidy indentation, remove unnecessary
 whitespace, and all that sort of stuff...?


Vim, emacs?

Best,
Regards



--

___
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 49, Issue 23
*


Beginners Digest, Vol 49, Issue 24

2012-07-21 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  automatically clean up Haskell code? (Brent Yorgey)
   2. Re:  automatically clean up Haskell code? (Christian Maeder)


--

Message: 1
Date: Fri, 20 Jul 2012 07:09:12 -0400
From: Brent Yorgey byor...@seas.upenn.edu
Subject: Re: [Haskell-beginners] automatically clean up Haskell code?
To: beginners@haskell.org
Message-ID: 20120720110912.ga32...@seas.upenn.edu
Content-Type: text/plain; charset=us-ascii

On Thu, Jul 19, 2012 at 06:19:36PM -0800, Christopher Howard wrote:
 Is there a program that can automatically clean up your Haskell code?
 That is, shrink to 80 columns, make tidy indentation, remove unnecessary
 whitespace, and all that sort of stuff...?

Try http://hackage.haskell.org/package/stylish%2Dhaskell .

-Brent



--

Message: 2
Date: Fri, 20 Jul 2012 13:54:36 +0200
From: Christian Maeder christian.mae...@dfki.de
Subject: Re: [Haskell-beginners] automatically clean up Haskell code?
To: Christopher Howard christopher.how...@frigidcode.com
Cc: Haskell Beginners beginners@haskell.org
Message-ID: 500946fc.7060...@dfki.de
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

You may want to try out (and complain afterwards)

  scan -i file.hs

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

scan does not break your lines that are longer than 80 chars, though, 
but it reports those.

C.

Am 20.07.2012 04:19, schrieb Christopher Howard:
 Is there a program that can automatically clean up your Haskell code?
 That is, shrink to 80 columns, make tidy indentation, remove unnecessary
 whitespace, and all that sort of stuff...?







--

___
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 49, Issue 24
*


Beginners Digest, Vol 49, Issue 25

2012-07-22 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  Where do you put your tests? (Michael Orlitzky)
   2. Re:  Where do you put your tests? (Magnus Therning)
   3. Re:  Where do you put your tests? (Brent Yorgey)
   4. Re:  Where do you put your tests? (Michael Orlitzky)
   5.  simple sound playback (Gnu/Linux) (Christopher Howard)
   6. Re:  Where do you put your tests? (Magnus Therning)


--

Message: 1
Date: Sat, 21 Jul 2012 13:50:46 -0400
From: Michael Orlitzky mich...@orlitzky.com
Subject: Re: [Haskell-beginners] Where do you put your tests?
To: beginners@haskell.org
Message-ID: 500aebf6.3020...@orlitzky.com
Content-Type: text/plain; charset=ISO-8859-1

On 07/19/2012 09:27 AM, damodar kulkarni wrote:
 
 Good because library dependencies are reduced, but bad because tests
 are somewhat disconnected from the functions they are testing.
 
 
 AFAIK, it's a good engineering practice to separate the tests from the
 code they are supposed to test. Code management issues will be there,
 but those can be taken care with the help of cabal like tool.
 That way, a person who wants to test will use the test-files and the one
 who doesn't want will be spared the trouble of separating tests from the
 intended function code.
 

This is the solution I'd prefer, but I quickly ran into a problem: if I
want to test internal (non-exported) functions, the tests need to be in
the same module as the code.

Is there a way around this?

(For now, I just put the code in the same file and depend on the test libs.)



--

Message: 2
Date: Sat, 21 Jul 2012 20:04:35 +0200
From: Magnus Therning mag...@therning.org
Subject: Re: [Haskell-beginners] Where do you put your tests?
To: Michael Orlitzky mich...@orlitzky.com
Cc: beginners@haskell.org
Message-ID:
CAAExw5sQ0DiH19T-R=ZxLfXauz9jdSnz+XFsmR=oseg7qjb...@mail.gmail.com
Content-Type: text/plain; charset=UTF-8

On Sat, Jul 21, 2012 at 7:50 PM, Michael Orlitzky mich...@orlitzky.com wrote:
 On 07/19/2012 09:27 AM, damodar kulkarni wrote:

 Good because library dependencies are reduced, but bad because tests
 are somewhat disconnected from the functions they are testing.


 AFAIK, it's a good engineering practice to separate the tests from the
 code they are supposed to test. Code management issues will be there,
 but those can be taken care with the help of cabal like tool.
 That way, a person who wants to test will use the test-files and the one
 who doesn't want will be spared the trouble of separating tests from the
 intended function code.


 This is the solution I'd prefer, but I quickly ran into a problem: if I
 want to test internal (non-exported) functions, the tests need to be in
 the same module as the code.

 Is there a way around this?

 (For now, I just put the code in the same file and depend on the test libs.)

A common issue.  I, and some others I've seen, have a FooInternal
module exporting *everything* for the tests, and a Foo module
exporting only the public API.

/M

-- 
Magnus Therning  OpenPGP: 0xAB4DFBA4
email: mag...@therning.org   jabber: mag...@therning.org
twitter: magthe   http://therning.org/magnus



--

Message: 3
Date: Sat, 21 Jul 2012 14:12:21 -0400
From: Brent Yorgey byor...@seas.upenn.edu
Subject: Re: [Haskell-beginners] Where do you put your tests?
To: beginners@haskell.org
Message-ID: 20120721181220.ga18...@seas.upenn.edu
Content-Type: text/plain; charset=us-ascii

On Sat, Jul 21, 2012 at 08:04:35PM +0200, Magnus Therning wrote:
 On Sat, Jul 21, 2012 at 7:50 PM, Michael Orlitzky mich...@orlitzky.com 
 wrote:
  On 07/19/2012 09:27 AM, damodar kulkarni wrote:
 
  Good because library dependencies are reduced, but bad because tests
  are somewhat disconnected from the functions they are testing.
 
 
  AFAIK, it's a good engineering practice to separate the tests from the
  code they are supposed to test. Code management issues will be there,
  but those can be taken care with the help of cabal like tool.
  That way, a person who wants to test will use the test-files and the one
  who doesn't want will be spared the trouble of separating tests from the
  intended function code.
 
 
  This is the solution I'd prefer, but I quickly ran into a problem: if I
  want to test internal (non-exported) functions, the tests need to be in
  the same module as the code.
 
  Is there a way around this?
 
  (For now, I just put the 

Beginners Digest, Vol 49, Issue 26

2012-07-23 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  Pb with toggleActionNew (Pierre Michallet)
   2. Re:  Pb with toggleActionNew (Brandon Allbery)
   3. Re:  Pb with toggleActionNew (Nick Vanderweit)
   4. Re:  simple sound playback (Gnu/Linux) (Stephen Tetley)


--

Message: 1
Date: Sun, 22 Jul 2012 16:46:56 +0200
From: Pierre Michallet p.michal...@free.fr
Subject: [Haskell-beginners] Pb with toggleActionNew
To: beginners haskell beginners@haskell.org
Message-ID: 8F8862782F1248EF96C8E6DFD996293F@medione9995867
Content-Type: text/plain; charset=iso-8859-1

I am trying to become acquainted with both haskell and Gtk thru the writing of 
small pieces of code exercising some Gtk functions.
Having had problems with the ToggleEntry function (unable to get the 
checked/non checked status - refer to chapter 7.2 of the Gtk2HS tutorial) I 
have tried to understand
the toggleAction thing.
So I have written this :

import  Graphics.UI.Gtk.ActionMenuToolbar.ToggleAction
...

togls::[ToggleAction]
togls = let stone = toggleActionNew STON Stones number Nothing  Nothing  
(myTog stone)   
   deste = toggleActionNew DEST Destination Nothing Nothing  
(myTog deste)  
  state = toggleActionNew STAT Board status Nothing Nothing  
(myTog state)
  in [stone,deste,state]

myTog::ToggleAction-IO()
myTog ta =  putStrLn (The name of the action is  ++ (toggleActionName ta))   

The compiler is not happy with this and sends back the following:

---

The function 'toggleActionNew' is applied to five arguments but its type 'String

  -String

  -Maybe String

  - Maybe stockId

  -IO ToggleAction
has only four.

---
To me, stone has 4 parameters (STON, Stones number, Nothing,Nothing) and a 
result (myTog stone) as in the definition given by the compiler.
I am using ghc-7.0.3
gthk+-bundle_2.16.2-20090601_win32
gtk-0.12.3.1 documentation

I am certainly missing something obvious to everybody but I could not solve it 
, so I would appreciate any help on this topic.

Thanks in advance

p.michal...@free.fr
 

-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120722/cb072eb2/attachment-0001.htm

--

Message: 2
Date: Sun, 22 Jul 2012 11:22:11 -0400
From: Brandon Allbery allber...@gmail.com
Subject: Re: [Haskell-beginners] Pb with toggleActionNew
To: Pierre Michallet p.michal...@free.fr
Cc: beginners haskell beginners@haskell.org
Message-ID:
CAKFCL4Xd+8GJJu=luiwqhmbvueydonk0oquxxb7ee759jue...@mail.gmail.com
Content-Type: text/plain; charset=utf-8

On Sun, Jul 22, 2012 at 10:46 AM, Pierre Michallet p.michal...@free.frwrote:

 **
 To me, stone has 4 parameters (STON, Stones number, Nothing,Nothing)
 and a result (myTog stone) as in the definition given by the compiler.


Yes.  So why are you trying to provide the result that it's supposed to
produce?

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120722/ce35e86e/attachment-0001.htm

--

Message: 3
Date: Sun, 22 Jul 2012 15:13:30 -0600
From: Nick Vanderweit nick.vanderw...@gmail.com
Subject: Re: [Haskell-beginners] Pb with toggleActionNew
To: beginners@haskell.org
Message-ID: 6369472.JAMQu0YQAV@euler
Content-Type: text/plain; charset=us-ascii

Besides the fact that you are trying to pass the result of toggleActionNew as 
an argument, you're going to end up with problems regarding the type signature 
of togls when you try to invoke toggleActionNew, whose type 

Beginners Digest, Vol 49, Issue 30

2012-07-28 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  List syntax (Stayvoid)
   2. Re:  List syntax (Brandon Allbery)
   3. Re:  List syntax (Stayvoid)
   4. Re:  List syntax (Lyndon Maydwell)
   5. Re:  List syntax (Christian Maeder)
   6.  cabal / haddock: view source with API (Christopher Howard)


--

Message: 1
Date: Fri, 27 Jul 2012 17:27:25 +0400
From: Stayvoid stayv...@gmail.com
Subject: [Haskell-beginners] List syntax
To: beginners@haskell.org
Message-ID:
CAK5fS_Hat3Or=jzw6qe3hwtvudyombn_wp0egkne81qkvvw...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

Hi,

Why can't we do this: [LT..GT]?
The following works:
['a'..'e']
['a' .. 'e']
[LT .. GT]

Cheers



--

Message: 2
Date: Fri, 27 Jul 2012 10:49:58 -0400
From: Brandon Allbery allber...@gmail.com
Subject: Re: [Haskell-beginners] List syntax
To: Stayvoid stayv...@gmail.com
Cc: beginners@haskell.org
Message-ID:
CAKFCL4W=1ue-ovo6ozhzpvjz3cuxxvte5xf-t9ozwkw5-1h...@mail.gmail.com
Content-Type: text/plain; charset=utf-8

On Fri, Jul 27, 2012 at 9:27 AM, Stayvoid stayv...@gmail.com wrote:

 Why can't we do this: [LT..GT]?


Because LT.. is the operator (.) in the module LT, and is unexpected
there.

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120727/62630d12/attachment-0001.htm

--

Message: 3
Date: Fri, 27 Jul 2012 18:53:47 +0400
From: Stayvoid stayv...@gmail.com
Subject: Re: [Haskell-beginners] List syntax
To: beginners@haskell.org
Message-ID:
cak5fs_frd398fbsk3jfkwzmve0xc78yzxi1fn06m93zy-n3...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

Thanks.



--

Message: 4
Date: Fri, 27 Jul 2012 23:01:20 +0800
From: Lyndon Maydwell maydw...@gmail.com
Subject: Re: [Haskell-beginners] List syntax
To: Stayvoid stayv...@gmail.com, Beginners Haskell
beginners@haskell.org
Message-ID:
cam5qztxbdej4q8jpqkaxtzm6-ptxcznnd0033wrvcp2feqj...@mail.gmail.com
Content-Type: text/plain; charset=UTF-8

On Fri, Jul 27, 2012 at 10:52 PM, Stayvoid stayv...@gmail.com wrote:
 Thanks.

 P.S. I think that you should send your answer to the list to show the
 others that this issue is solved.


Ah, I thought I replied to all. Well, here is my reply for the record :-)


Here's what I'm describing in a GHCi session:

  ? [LT..GT]

 interactive:2:2:
 Failed to load interface for `LT'
 Use -v to see a list of the files searched for.

 interactive:2:2:
 A section must be enclosed in parentheses thus: (LT.. GT)

I'm assuming that this was the error that you encountered when you
tried to use the syntax [LT..GT].

In my example I used a renamed module, but this also makes sense for a
module imported the usual way. I renamed the module so you could see
directly how an ambiguity could occur for 'LT'.

If you import a module you can rename it by using the 'as' keyword, in
this case, 'LT'. There is now an ambiguity between 'LT' = less than
and 'LT' = Data.List.

  ? import qualified Data.List as LT

  ? :i LT.map
 map :: (a - b) - [a] - [b] -- Defined in `GHC.Base'

Here is a demonstration of the renamed module in action.

  ? :i LT..

 Top level:
 Failed to load interface for `LT'
 Use -v to see a list of the files searched for.

And here is what I think is causing your error to be thrown - The
symbol '.' is being searched for in module LT in the same manner that
'map' was in the previous example, now given that there is no LT
module, it is failing.

This ambiguity might seem annoying, but it's not too bad since you can
just put some spaces in to resolve it.



--

Message: 5
Date: Fri, 27 Jul 2012 17:52:06 +0200
From: Christian Maeder christian.mae...@dfki.de
Subject: Re: [Haskell-beginners] List syntax
To: Lyndon Maydwell maydw...@gmail.com
Cc: Beginners Haskell beginners@haskell.org
Message-ID: 5012b926.1020...@dfki.de
Content-Type: text/plain; charset=UTF-8; format=flowed

In fact there is no ambiguity (but ghc does not bother to resolve this).

No legal expression can start with a (qualified) symbol like ., so 
since you used square brackets rather than round ones (to make a 
section) the resolution could be unique (by accepting an 

Beginners Digest, Vol 49, Issue 32

2012-07-30 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  Here's why functions should return functions
  (Ertugrul S?ylemez)


--

Message: 1
Date: Mon, 30 Jul 2012 06:38:40 +0200
From: Ertugrul S?ylemez e...@ertes.de
Subject: Re: [Haskell-beginners] Here's why functions should return
functions
To: beginners@haskell.org
Message-ID: 20120730063840.68d14...@tritium.streitmacht.eu
Content-Type: text/plain; charset=utf-8

Jay Sulzberger j...@panix.com wrote:

 There is, in most sub-systems of mathematics, whether like recent type
 theory or not, a general function, let us call it mcf which in Scheme
 notation may be defined by executing

 (define mcf
(lambda (a)
  (lambda (x) a)))

 Now in Haskell I know that one, perhaps the, parallel definition must
 result in a polymorphic function.

First let's ensure that we are talking about the same function.  I'm
reading mcf as make constant function.  From what I read the Haskell
equivalent would be this function:

const a _ = a

It may make it not fully polymorphic, but if you don't provide a type
signature, then the following fully polymorphic type will be inferred:

const :: a - b - a


 What is this definition?

Well, this is the constant function, though with slightly unusual (but
sensible) semantics for Scheme.  Because Scheme syntax requires explicit
currying the name make constant function would also be sensible.  It
is because of the lack of side effects that we call the function simply
'const' in Haskell.  Otherwise most functions would be prefixed with
make.


 What implicit constraints are on a?

None.


 Does lazy vs eager come in here?

Yes.  Even though you have written a curried version of 'const' there,
Scheme is still a strict language, which means that the result of the
inner lambda will depend on its argument 'x'.  This means:

-- Haskell:
const a ? = a

-- in other words:
loop = loop  -- an infinite loop
const a loop = a

; Scheme:
((mcf a) ?) = ?

(define (loop) (loop))  ; an infinite loop
((mcf a) (loop)) = (loop)

This is the semantic difference.  To relate this to lazy vs. eager
it's important to understand how a nonstrict language like Haskell is
usually evaluated:  Lazy evaluation will defer the evaluation of the
inner lambda's argument (which is an unnamed '_' here) until it is
required.  Since it is never required it is never evaluated and the
unevaluated thunk is garbage-collected immediately, unless it is used
elsewhere.

A strict language like Scheme is usually evaluated eagerly.  This means
that the inner lambda is not entered, until the argument is fully
evaluated.


 Are there options to ghc which might modify how Haskell handles the
 definition?

There are optimization flags, which could change the performance of the
definition, but a proper Haskell compiler like GHC must ensure that
semantics are not changed.


 Of course, my questions are too many and I hope just for some
 indications of the first things a beginner should study.

No worries.  I'm happy to help. =)


Greets,
Ertugrul

-- 
Not to be or to be and (not to be or to be and (not to be or to be and
(not to be or to be and ... that is the list monad.
-- next part --
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 836 bytes
Desc: not available
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120730/adf81b88/attachment-0001.pgp

--

___
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 49, Issue 32
*


Beginners Digest, Vol 49, Issue 35

2012-07-31 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  XmlPickler on ADT (Tim Perry)


--

Message: 1
Date: Tue, 31 Jul 2012 13:14:49 -0700
From: Tim Perry tim.v...@gmail.com
Subject: Re: [Haskell-beginners] XmlPickler on ADT
To: Haskell Beginners beginners@haskell.org
Message-ID:
cafvgasvbz1cnezt_fvrcjjlw75o56yjde-sfxy5dafx-h5h...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

I found the error. I used Renewable as the name of the XML element tag
when it should have been Renewables with a trailing s. Oops. Sorry for
the spam -- Tim



On Tue, Jul 31, 2012 at 10:55 AM, Tim Perry tim.v...@gmail.com wrote:

 Hi everyone,

 I'm trying to learn to write XmlPicklers.  I've been trying to follow the
 tutorial on the HaskelWiki, but it doesn't quite cover an issue I've run
 into.

 http://www.haskell.org/haskellwiki/HXT/Conversion_of_Haskell_data_from/to_XML

 I have a ADTs like so:

 data Plant = Plant

 { renewables :: [Renewable]

 , rewewableMonthly :: [RenewableMonthly]

 , waterHeating :: [WaterHeating]

 , hvac :: [HVAC]

 } deriving (Read, Show, Eq)

 data Renewable = Renewable

 { dcRating :: Double -- kW

 , annualTDV :: Double -- CA Energy Comm. TDV

 } deriving (Read, Show, Eq)

 data RenewableMonthly = RenewableMonthly

 { month :: Int

 , cost :: Double

 , demand :: Double

 , energy :: Double

 } deriving (Read, Show, Eq)

 data WaterHeating = WaterHeating

 { whName :: String  -- name for reference purposes.

 , whQuantity :: Int
 ...

 data HVAC = HVAC

 { slaStatus :: String  -- Specific leakage area 
 construction type.

 , newCFM50 :: Double   -- New building leakage in cubic 
 feet per minute.

 , existCFM50 :: Double


 I want to use an XmlPickler to read and write this.  The XML looks like
 this:

 Plant

   Renewables DCRating=8.4 AnnualTDV=0 /

   RenewableMonthly Month=1 Cost=0 Demand=0 Energy=0 /

   RenewableMonthly Month=2 Cost=0 Demand=0 Energy=0 /

   RenewableMonthly Month=3 Cost=0 Demand=0 Energy=0 /

   RenewableMonthly Month=4 Cost=0 Demand=0 Energy=0 /

   RenewableMonthly Month=5 Cost=0 Demand=0 Energy=0 /

   RenewableMonthly Month=6 Cost=0 Demand=0 Energy=0 /

   RenewableMonthly Month=7 Cost=0 Demand=0 Energy=0 /

   RenewableMonthly Month=8 Cost=0 Demand=0 Energy=0 /

   RenewableMonthly Month=9 Cost=0 Demand=0 Energy=0 /

   RenewableMonthly Month=10 Cost=0 Demand=0 Energy=0 /

   RenewableMonthly Month=11 Cost=0 Demand=0 Energy=0 /

   RenewableMonthly Month=12 Cost=0 Demand=0 Energy=0 /

   WaterHeating Name=Daikin Altherma HP Quantity=1 
 ConstructionStatus=New EnergyFactor=2.344 SolarFraction=0 
   HVAC SLAStatus=New NewCFM50=0 ExistCFM50=0 
 NewSLA=4.900953674316 ExistSLA=4.9 DuctStatus=New 

 Zone ...


 Running my code I get an error:

 -- (1) readDocument: start processing document 1101_11-001 Walsh.xml --
 (1) getXmlContents: content read and decoded for
 file:///fairoaks1/all_proj/1101%20PGE%20CAHP%2011-12/CRM/EProDataExtractPlanning/XML%20samples/1101_11-001%20Walsh.xml
 -- (1) getXmlContents' -- (1) readDocument: 1101_11-001 Walsh.xml (mime
 type: text/xml ) will be processed -- (1) readDocument: 1101_11-001
 Walsh.xml processed

 fatal error: document unpickling failed
 xpCheckEmptyContents: unprocessed XML content detected context: element
 Plant contents:

 Is it possible to write an XmlPickler for this?  Do I need to make
 Renewable, RenewableMonthly, WaterHeating, and HVAC all the same type with
 4 constructors and use xpAlt? Ideas?

 Thanks,
 Tim




-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120731/ad149d16/attachment.htm

--

___
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 49, Issue 35
*


Beginners Digest, Vol 50, Issue 3

2012-08-02 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  Resources to learn functional programming (Hilco Wijbenga)
   2. Re:  Resources to learn functional programming (Dudley Brooks)
   3. Re:  Resources to learn functional programming (David Hinkes)
   4. Re:  Resources to learn functional programming (Lorcan McDonald)
   5. Re:  Resources to learn functional programming (Arthur Clune)


--

Message: 1
Date: Wed, 1 Aug 2012 15:09:09 -0700
From: Hilco Wijbenga hilco.wijbe...@gmail.com
Subject: Re: [Haskell-beginners] Resources to learn functional
programming
To: Tim Perry tim.v...@gmail.com
Cc: Haskell Beginners beginners@haskell.org
Message-ID:
CAE1pOi1fSTcdNEgLs2-c=+kvkiyaweyvm+0jvptdww6b1sm...@mail.gmail.com
Content-Type: text/plain; charset=UTF-8

On 1 August 2012 14:23, Tim Perry tim.v...@gmail.com wrote:
 I think that you should work your way through Real World Haskell which is
 available free online. I thought it was worth-while enough that I bought the
 book and I regularly refer to it.
 http://book.realworldhaskell.org/

 Learn you a Haskell for Great Good is also a worth-while book.
 http://learnyouahaskell.com/

A very big +1 for this one. LYAHFGG really made it click for me. RWH
is an excellent book too but more for subsequent reading (at least for
me).

(I recently bought both LYAHFGG and RWH. The decision to buy was made
much easier by the fact that I was able to read them online first.)



--

Message: 2
Date: Wed, 01 Aug 2012 15:14:54 -0700
From: Dudley Brooks dbro...@runforyourlife.org
Subject: Re: [Haskell-beginners] Resources to learn functional
programming
To: Haskell Beginners beginners@haskell.org
Message-ID: 5019aa5e.4070...@runforyourlife.org
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

On 8/1/12 2:23 PM, Tim Perry wrote:

 I think that you should work your way through Real World Haskell
 which is available free online. I thought it was worth-while enough
 that I bought the book and I regularly refer to it.
 http://book.realworldhaskell.org/

 Learn you a Haskell for Great Good is also a worth-while book.
 http://learnyouahaskell.com/

The Haskell wikibook is also good, available online as HTML or PDF:

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

Personally, I found that Learn You a Haskell started to get obscure at 
about the chapter on monads, just where the most clarity is needed, and 
that the wikibook was clearer.  But different strokes for different 
folks.  (I haven't looked at that section of Real-World Haskell yet.)

--
Dudley



--

Message: 3
Date: Wed, 1 Aug 2012 15:15:01 -0700
From: David Hinkes david.hin...@gmail.com
Subject: Re: [Haskell-beginners] Resources to learn functional
programming
To: Hilco Wijbenga hilco.wijbe...@gmail.com
Cc: Haskell Beginners beginners@haskell.org
Message-ID:
CA+_CxFOgUNBuN6AwmE4Gvw65fkvtkaN8iLmYD4wa=cugsrp...@mail.gmail.com
Content-Type: text/plain; charset=utf-8

And LYAHFGG is nice on the eyes.

On Wed, Aug 1, 2012 at 3:09 PM, Hilco Wijbenga hilco.wijbe...@gmail.comwrote:

 On 1 August 2012 14:23, Tim Perry tim.v...@gmail.com wrote:
  I think that you should work your way through Real World Haskell which
 is
  available free online. I thought it was worth-while enough that I bought
 the
  book and I regularly refer to it.
  http://book.realworldhaskell.org/
 
  Learn you a Haskell for Great Good is also a worth-while book.
  http://learnyouahaskell.com/

 A very big +1 for this one. LYAHFGG really made it click for me. RWH
 is an excellent book too but more for subsequent reading (at least for
 me).

 (I recently bought both LYAHFGG and RWH. The decision to buy was made
 much easier by the fact that I was able to read them online first.)

 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners




-- 
David Hinkes
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120801/224ac63b/attachment-0001.htm

--

Message: 4
Date: Wed, 1 Aug 2012 23:15:01 +0100
From: Lorcan McDonald lor...@lorcanmcdonald.com
Subject: Re: [Haskell-beginners] Resources to learn functional
programming
To: David Hinkes david.hin...@gmail.com
Cc: Haskell Beginners beginners@haskell.org
Message-ID:

Beginners Digest, Vol 50, Issue 4

2012-08-03 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  Resources to learn functional programming (Patrick Redmond)
   2. Re:  Resources to learn functional programming
  (Homero Cardoso de Almeida)
   3. Re:  Resources to learn functional programming
  (Alexander Bernauer)
   4.  vector indexing time (Ivan Vyalov)
   5. Re:  vector indexing time (Alexander Dunlap)
   6. Re:  vector indexing time (Nick Vanderweit)


--

Message: 1
Date: Thu, 2 Aug 2012 06:30:26 -0400
From: Patrick Redmond plredm...@gmail.com
Subject: Re: [Haskell-beginners] Resources to learn functional
programming
To: Haskell Beginners beginners@haskell.org
Message-ID:
cahuea4h4lav2gcrnw_uhr43lqbqksuajfyowyhfczt8mizm...@mail.gmail.com
Content-Type: text/plain; charset=UTF-8

Although many resources have been mentioned here, I'd like to
recommend How To Design Programs, http://www.htdp.org/, which
approaches functional programming from a Scheme (Racket) perspective.
This book is how I learned functional programming and developed an
interest in Haskell.

In HTDP, higher order functions aren't introduced until you've been
taught how to write similar code without them. Then you learn that
your code can be abbreviated using things like map, foldl, foldr,
ormap, andmap, etc. The book moves into more complicated uses of
functions-as-data near the end.

Hope you find it useful,
Patrick


On Thu, Aug 2, 2012 at 4:03 AM, Arthur Clune art...@clune.org wrote:
 In a similar vein, I highly recommend Higher Order Perl by
 Mark-Jason Dominus. It presents most of these concepts in a more
 familiar setting. Don't worry if you don't know perl, if you know C++,
 you'll know enough to follow the book.

 Arthur

 --
 Arthur Clune art...@clune.org

 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners



--

Message: 2
Date: Thu, 2 Aug 2012 10:54:16 -0300
From: Homero Cardoso de Almeida homero...@gmail.com
Subject: Re: [Haskell-beginners] Resources to learn functional
programming
To: Patrick Redmond plredm...@gmail.com
Cc: Haskell Beginners beginners@haskell.org
Message-ID:
CAPv0Zwop0eUZj999E2uZQiyTN3VN3aqJEWWMNZKQHP7ty=n...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

Thanks for all the suggestions.

I was learning Haskell through LYAHFGG, and that's when I got the problem
with Higher Order functions. I'll take a look at all the resources posted.

Thanks again,
Homero Cardoso de Almeida


On Thu, Aug 2, 2012 at 7:30 AM, Patrick Redmond plredm...@gmail.com wrote:

 Although many resources have been mentioned here, I'd like to
 recommend How To Design Programs, http://www.htdp.org/, which
 approaches functional programming from a Scheme (Racket) perspective.
 This book is how I learned functional programming and developed an
 interest in Haskell.

 In HTDP, higher order functions aren't introduced until you've been
 taught how to write similar code without them. Then you learn that
 your code can be abbreviated using things like map, foldl, foldr,
 ormap, andmap, etc. The book moves into more complicated uses of
 functions-as-data near the end.

 Hope you find it useful,
 Patrick


 On Thu, Aug 2, 2012 at 4:03 AM, Arthur Clune art...@clune.org wrote:
  In a similar vein, I highly recommend Higher Order Perl by
  Mark-Jason Dominus. It presents most of these concepts in a more
  familiar setting. Don't worry if you don't know perl, if you know C++,
  you'll know enough to follow the book.
 
  Arthur
 
  --
  Arthur Clune art...@clune.org
 
  ___
  Beginners mailing list
  Beginners@haskell.org
  http://www.haskell.org/mailman/listinfo/beginners

 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners

-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120802/b7a6a76f/attachment-0001.htm

--

Message: 3
Date: Thu, 2 Aug 2012 16:19:01 +0200
From: Alexander Bernauer alex-hask...@copton.net
Subject: Re: [Haskell-beginners] Resources to learn functional
programming
To: beginners@haskell.org
Message-ID: 20120802141901.GB2608@apus
Content-Type: text/plain; charset=us-ascii

On Wed, Aug 01, 2012 at 05:53:36PM -0300, Homero 

Beginners Digest, Vol 50, Issue 7

2012-08-06 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  Using a concept from Category Theory to enable you to
  come back home after your function has taken you somewhere
  (Brent Yorgey)
   2. Re:  Using a concept from Category Theory to  enable you to
  come back home after your function has taken  you somewhere
  (Miguel Negrao)
   3. Re:  DPH installation and LLVM (Erik de Castro Lopo)


--

Message: 1
Date: Sun, 5 Aug 2012 08:37:30 -0400
From: Brent Yorgey byor...@seas.upenn.edu
Subject: Re: [Haskell-beginners] Using a concept from Category Theory
to enable you to come back home after your function has taken you
somewhere
To: beginners@haskell.org
Message-ID: 20120805123730.ga23...@seas.upenn.edu
Content-Type: text/plain; charset=iso-8859-1

On Sat, Aug 04, 2012 at 05:59:59PM +, Costello, Roger L. wrote:
 
  How to automatically get the inverse of a Haskell function?
 
 That's a great question. I don't know the answer to that. Anyone else have an 
 idea?

It is not possible in general... but on the other hand you can use
parametricity to pull some cool tricks.  See Janis Voigtl?nder's paper
from 2009, Bidirectionalization for free!
(http://www.iai.uni-bonn.de/~jv/popl09-2.pdf) which is a fun read.
You can even play with an implementation of it here:

  http://www-ps.iai.uni-bonn.de/cgi-bin/bff.cgi

-Brent



--

Message: 2
Date: Sun, 5 Aug 2012 14:05:58 +0100
From: Miguel Negrao miguel.negrao-li...@friendlyvirus.org
Subject: Re: [Haskell-beginners] Using a concept from Category Theory
to  enable you to come back home after your function has taken  
you
somewhere
To: beginners@haskell.org
Message-ID: fc3d31e0-d380-4485-a5ac-96b8f747c...@friendlyvirus.org
Content-Type: text/plain; charset=windows-1252

Hi Roger,

A 04/08/2012, ?s 18:59, Costello, Roger L. escreveu:

 Hi Miguel,
 
 First note that I am very much a beginner at Category Theory. I am just 
 sharing what I learn.

Yes I understand that, but what I was trying to say is that I don?t think that 
this is much related with category theory. 

 
 How do you know that a Haskell function is injective? I don't think it's 
 possible to write a function which checks if another function is injective 
 or not .
 
 A function is injective if each input value (domain) yields a different 
 output value (codomain). So if the set of inputs is finite, then it should be 
 possible to write a function that loops over each input value and checks that 
 its output is distinct from all other outputs.

Yes, but very few functions have finite domains, and if they do and it?s big it 
would take a long time to test it. That is not a technique that can be used in 
practice I think.

Brent wrote:
 It is not possible in general... but on the other hand you can use
 parametricity to pull some cool tricks.  See Janis Voigtl?nder's paper
 from 2009, Bidirectionalization for free!
 (http://www.iai.uni-bonn.de/~jv/popl09-2.pdf) which is a fun read.
 You can even play with an implementation of it here:
 
  http://www-ps.iai.uni-bonn.de/cgi-bin/bff.cgi
 
 -Brent

Yes, I think that was the paper I had seen. Interesting stuff.

best,
Miguel Negr?o


--

Message: 3
Date: Mon, 6 Aug 2012 18:55:31 +1000
From: Erik de Castro Lopo mle...@mega-nerd.com
Subject: Re: [Haskell-beginners] DPH installation and LLVM
To: beginners@haskell.org
Message-ID: 20120806185531.c89910a9cacd7e06f6341...@mega-nerd.com
Content-Type: text/plain; charset=UTF-8

listig...@gmail.com wrote:

 Since I haven't gotten any further answers I'm trying my luck again?
 
 Does anyone have an idea how I can get the llvm backend to work? My 
 configuration is:
 
 Mac OS X 10.7.4
 XCode 4.3.3 (with Command Line Tools installed)
 Haskell Platform 2012.2.0.0 32 bit
 llvm (via Homebrew)

DPH is not really a beginners topic. Maybe you should try the haskell-cafe
list.

Erik
-- 
--
Erik de Castro Lopo
http://www.mega-nerd.com/



--

___
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 50, Issue 7



Beginners Digest, Vol 50, Issue 11

2012-08-11 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  what is a qualified type? (Heinrich Apfelmus)
   2.  cabal errors.. (Gregory Guthrie)
   3. Re:  cabal errors.. (Stephen Tetley)


--

Message: 1
Date: Fri, 10 Aug 2012 13:29:47 +0200
From: Heinrich Apfelmus apfel...@quantentunnel.de
Subject: Re: [Haskell-beginners] what is a qualified type?
To: beginners@haskell.org
Message-ID: k02rba$ode$1...@dough.gmane.org
Content-Type: text/plain; charset=UTF-8; format=flowed

Christopher Howard wrote:
 In short, what is a qualified type and how is it used? (Any examples
 would be appreciated.)
 
 I feel somewhat embarrassed asking, as I used to know. I dropped Haskell
 a while ago and am just now picking it up again, and unfortunately I
 have forgotten many concepts.
 
 If someone could point me to the appropriate tutorial that might be
 enough. For some reason, all my StartPage searches are only bringing me
 to documents that assume I already understand qualified types, or to
 books I can't afford to buy.

This is a type:

[a] - a

This is a qualified type:

Num a = [a] - a

You can say that qualified types are types that include constraints via 
the  =  symbol.

In Haskell, you will mostly see type class constraints, but there are 
other possibilities as well. They are all grouped together in the notion 
of qualified types.

http://www.haskell.org/haskellwiki/Research_papers/Type_systems#Qualified_types


As a practicing Haskell programmer, you don't actually need to know how 
the theory of qualified types works. The only thing you need to be aware 
of the expression ambiguous constraint, because that's an occasional 
error message in GHC. Here an example:

Show a = Int - Bool   -- ambiguous constraint


Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com




--

Message: 2
Date: Fri, 10 Aug 2012 21:14:18 -0500
From: Gregory Guthrie guth...@mum.edu
Subject: [Haskell-beginners] cabal errors..
To: beginners@haskell.org beginners@haskell.org
Message-ID:
08ef9da445c4b5439c4733e1f35705ba01e265dd1...@mail.cs.mum.edu
Content-Type: text/plain; charset=us-ascii

I am (again) running into cabal install issues; which have been all too common 
for me.

In this case as an example, I tried this:
   C:\Users\haskellCabal install buildwrapper
  .
 buildwrapper-0.6.0 depends on regex-tdfa-1.1.8 which failed to install.
 regex-tdfa-1.1.8 failed during the building phase. The exception was:
 ExitFailure 1

So I tried this:
 C:\Users\haskellcabal install regex-tdfa
 Resolving dependencies...
 In order, the following would be installed:
 regex-base-0.93.2 (reinstall) changes: array-0.3.0.2 - 0.4.0.0, 
base-4.3.1.0
 - 4.5.0.0, bytestring-0.9.1.10 - 0.9.2.1, containers-0.4.0.0 - 0.4.2.1,
 mtl-2.0.1.0 - 2.1.2
 regex-tdfa-1.1.8 (new package)
 cabal: The following packages are likely to be broken by the reinstalls:
 regex-posix-0.95.1
 regex-compat-0.95.1
 haskell-platform-2011.3.0.0
 regex-posix-0.94.4
 regex-compat-0.93.1
 haskell-platform-2011.2.0.1
 regex-posix-0.95.1
 regex-compat-0.95.1
 haskell-platform-2012.2.0.0
 Use --force-reinstalls if you want to install anyway.

So what to do?
Last time I got into a situation like this I tried to start-over with cabal, 
remove all local cache and rebuild the library.
From a suggestion in SO; delete the ~/ghc  ~/cabal files and restart cabal, 
by a cabal install cabal-install.

Didn't help much, still stuck. Any hints?

I find that library issues like this with cabal are the biggest time-soak I 
have with using Haskell, and I usually have to abandon attempts to try some new 
library for various examples.

Ghc-pkg check lists lots of warnings, but all from haddock-html or 
haddock-interface; not sure what to make of that but I think it just means that 
somehow documentation was not installed for these packages.

cabal -V
cabal-install version 0.14.0
using version 1.14.0 of the Cabal library
GHCi version 7.4.1
HaskellPlatform-2012.2.0.0
---


-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120810/31721615/attachment.htm

--

Message: 3
Date: Sat, 11 Aug 2012 07:00:50 +0100
From: Stephen Tetley stephen.tet...@gmail.com
Subject: Re: [Haskell-beginners] cabal errors..
To: 

Beginners Digest, Vol 50, Issue 12

2012-08-12 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  cabal errors.. (Brandon Allbery)
   2.  Cabal error (Gregory Guthrie)


--

Message: 1
Date: Sat, 11 Aug 2012 10:31:41 -0400
From: Brandon Allbery allber...@gmail.com
Subject: Re: [Haskell-beginners] cabal errors..
To: Stephen Tetley stephen.tet...@gmail.com
Cc: Gregory Guthrie guth...@mum.edu,  beginners@haskell.org
beginners@haskell.org
Message-ID:
CAKFCL4WZb7+LhgVqUFLmdTkdcnV=o6zort+6-buohzbk3rb...@mail.gmail.com
Content-Type: text/plain; charset=utf-8

On Sat, Aug 11, 2012 at 2:00 AM, Stephen Tetley stephen.tet...@gmail.comwrote:

 From the cabal file accessible on Hackage it looks like you need to
 build regex-tfda with the build flag base4.


cabal-install should be figuring that out for itself unless the versions of
prerequisites are specified incorrectly.


 I don't uses cabal-install so can't say how to send it build flags


--flags=flag1[,flag2,...]

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120811/ffef5489/attachment-0001.htm

--

Message: 2
Date: Sat, 11 Aug 2012 23:37:16 -0500
From: Gregory Guthrie guth...@mum.edu
Subject: [Haskell-beginners] Cabal error
To: beginners@haskell.org beginners@haskell.org
Message-ID:
08ef9da445c4b5439c4733e1f35705ba01e265dd1...@mail.cs.mum.edu
Content-Type: text/plain; charset=us-ascii

I get the following Cabal install error:

 C:\Users\haskellcabal install buildwrapper
 Resolving dependencies...
 Configuring regex-tdfa-1.1.8...
 Warning: This package indirectly depends on multiple versions of the same
 package. This is highly likely to cause a compile failure.

If true, doesn't this mean that the regex-tdfa package has misconfigured 
dependencies?

---


-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120811/9822b44d/attachment-0001.htm

--

___
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 50, Issue 12
*


Beginners Digest, Vol 50, Issue 14

2012-08-14 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  cabal install errors (Gregory Guthrie)
   2. Re:  cabal install errors (Stephen Tetley)
   3. Re:  cabal install errors (Gregory Guthrie)
   4. Re:  cabal install errors (Stephen Tetley)
   5. Re:  cabal install errors (Henk-Jan van Tuyl)
   6. Re:  cabal install errors (Gregory Guthrie)
   7. Re:  cleanest way to unwrap a list? (Jack Henahan)
   8. Re:  cleanest way to unwrap a list? (Christopher Howard)
   9. Re:  cleanest way to unwrap a list? (Jack Henahan)


--

Message: 1
Date: Mon, 13 Aug 2012 07:31:19 -0500
From: Gregory Guthrie guth...@mum.edu
Subject: Re: [Haskell-beginners] cabal install errors
To: beginners@haskell.org beginners@haskell.org
Message-ID:
08ef9da445c4b5439c4733e1f35705ba01e265dd1...@mail.cs.mum.edu
Content-Type: text/plain; charset=us-ascii

I didn't get any concrete remedy for this, or its underlying cause.

Does it mean that this package is incompatible with others currently installed, 
and I am supposed to make a choice to uninstall or break them by forcing this, 
or ...???

---
 I tried this:
  C:\Users\haskellcabal install regex-tdfa
  Resolving dependencies...
  In order, the following would be installed:
  regex-base-0.93.2 (reinstall) changes: array-0.3.0.2 - 0.4.0.0, 
 base-4.3.1.0
  - 4.5.0.0, bytestring-0.9.1.10 - 0.9.2.1, containers-0.4.0.0 - 
 0.4.2.1,
  mtl-2.0.1.0 - 2.1.2
  regex-tdfa-1.1.8 (new package)
  cabal: The following packages are likely to be broken by the reinstalls:
  regex-posix-0.95.1
  regex-compat-0.95.1
  haskell-platform-2011.3.0.0
  regex-posix-0.94.4
  regex-compat-0.93.1
  haskell-platform-2011.2.0.1
  regex-posix-0.95.1
  regex-compat-0.95.1
  haskell-platform-2012.2.0.0
  Use --force-reinstalls if you want to install anyway.
 
 So what to do?
 cabal -V
 cabal-install version 0.14.0
 using version 1.14.0 of the Cabal library GHCi version 7.4.1
 HaskellPlatform-2012.2.0.0
 ---



--

Message: 2
Date: Mon, 13 Aug 2012 17:40:03 +0100
From: Stephen Tetley stephen.tet...@gmail.com
Subject: Re: [Haskell-beginners] cabal install errors
To: Gregory Guthrie guth...@mum.edu
Cc: beginners@haskell.org beginners@haskell.org
Message-ID:
cab2tprbwyfw5rtn-ja7ceibhgxxlzccvzsv8tex7o_xiz_5...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

The latest regex-tdfa is compatible with with the packages you have
installed, but cabal-install evidently wants to update all of
regex-tdfa's dependencies which thus breaks things.

Presumably cabal-install has an option not to transitively update
dependencies? As I don't use cabal-install I don't know it myself.



--

Message: 3
Date: Mon, 13 Aug 2012 11:41:46 -0500
From: Gregory Guthrie guth...@mum.edu
Subject: Re: [Haskell-beginners] cabal install errors
To: Stephen Tetley stephen.tet...@gmail.com
Cc: beginners@haskell.org beginners@haskell.org
Message-ID:
08ef9da445c4b5439c4733e1f35705ba01e265dd1...@mail.cs.mum.edu
Content-Type: text/plain; charset=us-ascii

Wouldn't this indicate some errors in the cabal install setup with the package?

So the solution is to get the package, and install directly?
Thanks.

---
 Subject: Re: [Haskell-beginners] cabal install errors
 
 The latest regex-tdfa is compatible with with the packages you have 
 installed, but cabal-
 install evidently wants to update all of regex-tdfa's dependencies which thus 
 breaks things.
 
 Presumably cabal-install has an option not to transitively update 
 dependencies? As I don't use
 cabal-install I don't know it myself.



--

Message: 4
Date: Mon, 13 Aug 2012 18:38:24 +0100
From: Stephen Tetley stephen.tet...@gmail.com
Subject: Re: [Haskell-beginners] cabal install errors
To: Gregory Guthrie guth...@mum.edu
Cc: beginners@haskell.org beginners@haskell.org
Message-ID:
CAB2TPRBhViLhh-1Uk-iAQs67ioFT5++4+rLxax1WO+PqK3V=a...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

The .cabal file in regex-tdfa is pretty relaxed about version numbers,
so I don't see see an error there.

If it were me I'd install it form local with runhaskell Setup.hs
configure; runhaskell Setup.hs build; runhaskell Setup.hs install



--

Message: 5
Date: Mon, 

Beginners Digest, Vol 50, Issue 15

2012-08-14 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  cabal install errors (Carlos J. G. Duarte)
   2. Re:  cabal install errors (Benjamin Edwards)
   3. Re:  cleanest way to unwrap a list? (Carlos J. G. Duarte)
   4. Re:  cleanest way to unwrap a list? (Tim Perry)
   5. Re:  cleanest way to unwrap a list? (Carlos J. G. Duarte)


--

Message: 1
Date: Tue, 14 Aug 2012 11:54:35 +0100
From: Carlos J. G. Duarte carlos.j.g.dua...@gmail.com
Subject: Re: [Haskell-beginners] cabal install errors
To: beginners@haskell.org
Message-ID: 502a2e6b.8070...@gmail.com
Content-Type: text/plain; charset=us-ascii

An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120814/5bc176de/attachment-0001.htm

--

Message: 2
Date: Tue, 14 Aug 2012 13:08:49 +0100
From: Benjamin Edwards edwards.b...@gmail.com
Subject: Re: [Haskell-beginners] cabal install errors
To: Carlos J. G. Duarte carlos.j.g.dua...@gmail.com
Cc: beginners@haskell.org
Message-ID:
can6k4nj5oz2e994pv8qdn89c1emhpx5-a191f5ettzkqu8u...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

I think one point bears repeating: cabal is a build system, really. It does
a good enough job of that. It is a *terrible* package manager and using it
as one I think is a classic mistake that the community needs to address.

My two-penneth worth is this:

Use cabal-dev, or hsenv, for *everything* and 99% of your woes will go
away. The the only thing I do when getting haskell up and running is to get
cabal-dev installed and it's dependencies in the cabal per user pkg store
and then cabal-dev sandboxes for everything from then on.
On Aug 14, 2012 11:57 AM, Carlos J. G. Duarte carlos.j.g.dua...@gmail.com
wrote:

  On 08/13/12 22:19, Gregory Guthrie wrote:

 Thanks, I'll try that, but it looks like it could be a lot of maintenance and 
 manual cleanup!

 I haven't knowingly done any manual upgrades of core packages, but I have 
 done updates as asked by cabal when it thinks the database is getting old. 
 I have had such pedestrian usage that I would not have expected to have 
 goofed up the database!  :-)

 Cabal seems to be more troublesome that other various *package managers* like 
 apt, etc...


 Please see this:
 http://ivanmiljenovic.wordpress.com/2010/03/15/repeat-after-me-cabal-is-not-a-package-manager/

 But yes, cabal or not, I agree that there should be a better system for
 managing haskell packages, like pip, gem or cpan... but that boils down to
 the problem that some has to do it, and people who are able to do it** are
 often too busy for that.

 ** and that doesn't include me, as I'm just starting to explore Haskell on
 my spare time.

 All in all, cabal suits me even with its idiosyncrasies.


 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners


-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120814/4fb0d351/attachment-0001.htm

--

Message: 3
Date: Tue, 14 Aug 2012 19:05:56 +0100
From: Carlos J. G. Duarte carlos.j.g.dua...@gmail.com
Subject: Re: [Haskell-beginners] cleanest way to unwrap a list?
To: beginners@haskell.org
Message-ID: 502a9384.9090...@gmail.com
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Ok, you all have been showing examples of running functions over 
elements. Add one, append value, and so on.
This works well if there's one or more operations to apply indistinctly 
to a number of elements.

Now, what if we just want to make a single operation to a single element?
For example, let's say I have this square matrix
[[1,2,3],
  [4,5,6],
  [7,8,9]]

how can we increment the value 5 (position 2,2) *and* decrement the 
value 7 (position 3,1)?

This is a made up example of course, I just want to see / learn if 
there's a way to apply a function to a specific subset of elements.

On 08/14/12 00:06, Jack Henahan wrote:
 Equally,

  let map' = map . map
  map' (+1) . map (++[3]) $ [[1,2],[3,4]]
  -- [[2,3,4],[4,5,4]]

 And you can really keep stacking those up. I think this approach will be 
 cleaner in the long run.

 For instance, let's start naming our parts.
 
 let list = [[1,2],[3,4]]
 let map' = map . map
 let addOne = map' (+1)
 let appendThree = map (++[3])
 let reverseInner = map reverse

 So, 

Beginners Digest, Vol 50, Issue 16

2012-08-15 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  cleanest way to unwrap a list? (Peter Hall)
   2. Re:  cleanest way to unwrap a list? (Nick Vanderweit)
   3. Re:  cabal install errors (damodar kulkarni)


--

Message: 1
Date: Tue, 14 Aug 2012 23:59:46 +0100
From: Peter Hall peter.h...@memorphic.com
Subject: Re: [Haskell-beginners] cleanest way to unwrap a list?
To: Carlos J. G. Duarte carlos.j.g.dua...@gmail.com
Cc: beginners@haskell.org
Message-ID:
CAA6hAk5ii7q2ptZPOU9ALm0U4X+Ofa_0UcqBPAuk9NKqwy8U=q...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

This is a bit more functional. The coordinates are the opposite way
around, and it can probably be expressed a bit more concisely, but
I'll leave that to you. This is the basic idea.

-- maps over a list supplying also the 'index'
mapi f = map (uncurry f) . zip [0..]

-- maps over a list supplying also the coordinate pair
mapii f a = mapi f' a
where f' i x = mapi (curry f $ i) x



m0 = [[1,2,3], [4,5,6], [7,8,9]]

f (1,1) a = a+1
f (0,2) a = a-1
f (_,_) a = a


mapii f m0 -- [[1,2,3],[4,6,6],[6,8,9]]


Peter


On 14 August 2012 22:50, Carlos J. G. Duarte
carlos.j.g.dua...@gmail.com wrote:

 I know it's doable. I was asking if there's a practical / elegant  way to do
 it.
 I see a lot of Haskell elegance when the matter is defining math formulas,
 running functions over elements, and so on. But it seems most of that
 elegance goes away when the problem derails a bit.

 Now for my problem I come up with this:

 modify mat x y f =
   let (lrows, row, rrows) = getpart mat x
   (lcols, col, rcols) = getpart row y
   in lrows ++ [lcols ++ [f col] ++ rcols] ++ rrows
   where
 getpart xs x = let (ls, r:rs) = splitAt x xs in (ls, r, rs)

 m0 = [[1,2,3], [4,5,6], [7,8,9]]

 main = do
   print m0
   let m1 = modify m0 1 1 succ
   let m2 = modify m1 2 0 pred
   print m2

 Which is a bit awkward considering the ease it is done in other languages.


 On 08/14/12 19:35, Tim Perry wrote:

 There is a way. Please try to figure it out and if you fail post back with
 your code and we can help you from there.



 On Tue, Aug 14, 2012 at 11:05 AM, Carlos J. G. Duarte
 carlos.j.g.dua...@gmail.com wrote:

 Ok, you all have been showing examples of running functions over elements.
 Add one, append value, and so on.
 This works well if there's one or more operations to apply indistinctly to
 a number of elements.

 Now, what if we just want to make a single operation to a single element?
 For example, let's say I have this square matrix
 [[1,2,3],
  [4,5,6],
  [7,8,9]]

 how can we increment the value 5 (position 2,2) *and* decrement the value
 7 (position 3,1)?

 This is a made up example of course, I just want to see / learn if there's
 a way to apply a function to a specific subset of elements.


 On 08/14/12 00:06, Jack Henahan wrote:

 Equally,

  let map' = map . map
  map' (+1) . map (++[3]) $ [[1,2],[3,4]]
  -- [[2,3,4],[4,5,4]]

 And you can really keep stacking those up. I think this approach will be
 cleaner in the long run.

 For instance, let's start naming our parts.
 let list = [[1,2],[3,4]]
 let map' = map . map
 let addOne = map' (+1)
 let appendThree = map (++[3])
 let reverseInner = map reverse

 So, from here we can do the following:
 list
 -- [[1,2],[3,4]]

 -- the first example
 addOne list
 -- [[2,3],[4,5]]
 -- now the second example
 addOne . appendThree $ list
 -- [[2,3,4],[4,5,4]]

 -- now add one to all members of the list, append three to the list,
 reverse the inner lists,
 -- then add one to all members of the new list

 addOne . reverseInner . appendThree . addOne $ list
 -- [[4,4,3],[4,6,5]]

 Now how would you construct that as a list comprehension? With the method
 I've proposed, you need
 only use map to operate on the nested lists themselves and map' to
 operate on the elements of those
 lists.

 
 Jack Henahan
 jhena...@uvm.edu

 On Aug 13, 2012, at 6:41 PM, Christopher Howard
 christopher.how...@frigidcode.com wrote:

 On 08/12/2012 09:37 PM, Shakthi Kannan wrote:

 Hi,

 --- On Mon, Aug 13, 2012 at 10:51 AM, Christopher Howard
 christopher.how...@frigidcode.com wrote:
 | Say, for example, I have the list
 | [[1,2],[3,4]] and want to add 1 to each inner element, resulting in
 | [[2,3],[4,5]].
 \--

 Like this?

 ghci let xxs = [[1,2], [3,4]]

 ghci [ [ x+1 | x - xs] | xs - xxs ]
 [[2,3],[4,5]]

Beginners Digest, Vol 50, Issue 17

2012-08-16 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  cabal install errors (Benjamin Edwards)
   2. Re:  cabal install errors (damodar kulkarni)
   3.  source code for Generics for the Masses (Michael Litchard)
   4.  Error compiling OpenGL tutorial part 2 (Darren Grant)


--

Message: 1
Date: Wed, 15 Aug 2012 12:04:15 +0100
From: Benjamin Edwards edwards.b...@gmail.com
Subject: Re: [Haskell-beginners] cabal install errors
To: damodar kulkarni kdamodar2...@gmail.com
Cc: haskellbeginners beginners@haskell.org
Message-ID:
can6k4nhm7rv3r9rudpprl7fpfpe_nawuwos3sjk26ndfmua...@mail.gmail.com
Content-Type: text/plain; charset=windows-1252

Ironically enough, cabal is an acronym: Common Architecture for Building
Applications and Libraries. Look ma, no packages! It is shame that almost
every new-comer gets burnt by this in one way or another. I might have a
crack at suggesting some re-writes, or extra caveats to the cabal docs.
On Aug 15, 2012 5:39 AM, damodar kulkarni kdamodar2...@gmail.com wrote:


 Please see this:
 http://ivanmiljenovic.wordpress.com/2010/03/15/repeat-after-me-cabal-is-not-a-package-manager/


 it is unfortunately true that cabal documentation is very misleading to
 many, especially the beginners ...
 that's why so many of us need to repeat after-an-expert that
 cabal-is-not-a-package-manager ...

 But now take a look at how many times the cabal user guide mentions the
 term package in its documentation, it is very easy to get misled...

 Cabal specifies a standard way in which Haskell libraries and applications
 can be *packaged* so that it is easy for consumers to use them, or *
 re-package* them, regardless of the Haskell implementation or
 installation platform.

 Cabal defines a common interface ? the *Cabal package* ? between *package
 authors, builders and users*. There is a library to help package authors
 implement this interface, and a tool to enable developers, builders and
 users *to work with Cabal packages*.

taken from http://www.haskell.org/cabal/users-guide/

 cabal should have been called haskell-make or hmake or something alike...

 thanks Benjamin, for the cabal-dev, hsenv tip though.

 -Damodar


 On Tue, Aug 14, 2012 at 5:38 PM, Benjamin Edwards 
 edwards.b...@gmail.comwrote:

 I think one point bears repeating: cabal is a build system, really. It
 does a good enough job of that. It is a *terrible* package manager and
 using it as one I think is a classic mistake that the community needs to
 address.

 My two-penneth worth is this:

 Use cabal-dev, or hsenv, for *everything* and 99% of your woes will go
 away. The the only thing I do when getting haskell up and running is to get
 cabal-dev installed and it's dependencies in the cabal per user pkg store
 and then cabal-dev sandboxes for everything from then on.
 On Aug 14, 2012 11:57 AM, Carlos J. G. Duarte 
 carlos.j.g.dua...@gmail.com wrote:

  On 08/13/12 22:19, Gregory Guthrie wrote:

 Thanks, I'll try that, but it looks like it could be a lot of maintenance 
 and manual cleanup!

 I haven't knowingly done any manual upgrades of core packages, but I have 
 done updates as asked by cabal when it thinks the database is getting 
 old. I have had such pedestrian usage that I would not have expected to 
 have goofed up the database!  :-)

 Cabal seems to be more troublesome that other various *package managers* 
 like apt, etc...


 Please see this:
 http://ivanmiljenovic.wordpress.com/2010/03/15/repeat-after-me-cabal-is-not-a-package-manager/

 But yes, cabal or not, I agree that there should be a better system for
 managing haskell packages, like pip, gem or cpan... but that boils down to
 the problem that some has to do it, and people who are able to do it** are
 often too busy for that.

 ** and that doesn't include me, as I'm just starting to explore Haskell
 on my spare time.

 All in all, cabal suits me even with its idiosyncrasies.


 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners


 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners






-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120815/09e28ac3/attachment-0001.htm

--

Message: 2
Date: Wed, 15 Aug 2012 21:36:42 +0530

Beginners Digest, Vol 50, Issue 19

2012-08-16 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  convert to fixed length Int (Christopher Howard)
   2. Re:  convert to fixed length Int (Carlos J. G. Duarte)
   3. Re:  cabal install errors  issues (Antoine Latter)
   4. Re:  cabal install errors  issues (Gregory Guthrie)
   5. Re:  cabal install errors  issues (Antoine Latter)
   6. Re:  cabal install errors  issues (Brandon Allbery)
   7. Re:  cabal install errors  issues (Gregory Guthrie)
   8. Re:  cabal install errors  issues (Antoine Latter)
   9. Re:  cabal install errors  issues (Gregory Guthrie)


--

Message: 1
Date: Thu, 16 Aug 2012 16:42:08 -0800
From: Christopher Howard christopher.how...@frigidcode.com
Subject: [Haskell-beginners] convert to fixed length Int
To: Haskell Beginners beginners@haskell.org
Message-ID: 502d9360.8070...@frigidcode.com
Content-Type: text/plain; charset=iso-8859-1

Hi. In Haskell, how would I go about converting from a Double (or Float)
type to a Data.Int.Int8, Data.Int.Int16, and so forth? (Of course,
expecting rounding and damage to out of range values.)

I was playing around with signal generation using trig functions (hence
the floating types) but the actual output has to be Int16.

-- 
frigidcode.com
indicium.us

-- next part --
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 554 bytes
Desc: OpenPGP digital signature
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120816/10ff76fd/attachment-0001.pgp

--

Message: 2
Date: Fri, 17 Aug 2012 02:06:14 +0100
From: Carlos J. G. Duarte carlos.j.g.dua...@gmail.com
Subject: Re: [Haskell-beginners] convert to fixed length Int
To: beginners@haskell.org
Message-ID: 502d9906.30...@gmail.com
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

On 08/17/12 01:42, Christopher Howard wrote:
 Hi. In Haskell, how would I go about converting from a Double (or Float)
 type to a Data.Int.Int8, Data.Int.Int16, and so forth? (Of course,
 expecting rounding and damage to out of range values.)

 I was playing around with signal generation using trig functions (hence
 the floating types) but the actual output has to be Int16.



Don't know if there's a better or correct way, but this seems to work:

ghci let c = (round 256.6) :: Int16
ghci :type c
c :: Int16

It rolls over at overflow:

ghci let c = (round 65537) :: Int16
ghci c
1





--

Message: 3
Date: Thu, 16 Aug 2012 21:21:56 -0500
From: Antoine Latter aslat...@gmail.com
Subject: Re: [Haskell-beginners] cabal install errors  issues
To: Gregory Guthrie guth...@mum.edu
Cc: beginners@haskell.org beginners@haskell.org
Message-ID:
cakjsnqhe-wmtndmyjo0b1rqtwxvetbs3qxiieqfonmkay_b...@mail.gmail.com
Content-Type: text/plain; charset=UTF-8

On Thu, Aug 16, 2012 at 8:18 AM, Gregory Guthrie guth...@mum.edu wrote:
 Thanks for the advice and pointers, I will try to make this transition, but 
 it looks like it is not so simple.

 Trying to bootstrap into cabal-dev seems to require some external 
 installations as well;

 cabal install cabal-dev --force-reinstalls

Maybe I'm missing some context, but is there a reason you're using the
--fore-reinstalls flag? If you didn't pass that then 'cabal' maybe
would not try to re-install the 'network' package and you wouldn't run
into this.

Antoine



--

Message: 4
Date: Thu, 16 Aug 2012 21:30:25 -0500
From: Gregory Guthrie guth...@mum.edu
Subject: Re: [Haskell-beginners] cabal install errors  issues
To: Antoine Latter aslat...@gmail.com
Cc: beginners@haskell.org beginners@haskell.org
Message-ID:
08ef9da445c4b5439c4733e1f35705ba01e267667...@mail.cs.mum.edu
Content-Type: text/plain; charset=utf-8

Yes, because a simple cabal install failed, and said the only way to do it 
was to force-installs.

But if this is a dependency, wouldn't it be requires (or not) either way?

---
 -Original Message-
  Trying to bootstrap into cabal-dev seems to require some external
  installations as well;
 
  cabal install cabal-dev --force-reinstalls
 
 Maybe I'm missing some context, but is there a reason you're using the 
 --fore-reinstalls
 flag? If you didn't pass that then 'cabal' maybe would not try to re-install 
 the 'network'
 package and you wouldn't run into this.

--

Message: 5
Date: Thu, 16 Aug 2012 21:36:54 -0500
From: 

Beginners Digest, Vol 50, Issue 20

2012-08-17 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  cabal install errors  issues (Andres L?h)
   2.  99problems: different response from ghci --runhaskell /
  ghc (GiGi)
   3. Re:  99problems: different response from ghci -- runhaskell
  / ghc (Andres L?h)


--

Message: 1
Date: Fri, 17 Aug 2012 10:16:34 +0200
From: Andres L?h andres.l...@googlemail.com
Subject: Re: [Haskell-beginners] cabal install errors  issues
To: Antoine Latter aslat...@gmail.com
Cc: Gregory Guthrie guth...@mum.edu,  beginners@haskell.org
beginners@haskell.org
Message-ID:
caljd_v5edgzm-3xf43p7rwdko5u_aj8cpmgnuxc_kby7v4d...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

Hi.

Sorry for singling out this one message of the thread to reply to a
bunch of messages.

 Can you try upgrading cabal-install to see if the new solver handles
 it better? I think the new version works with what is in the platform.
 If you also get errors there might be ways to make it go ...

I just tried installing cabal-dev on a clean platform, and I can
confirm it doesn't work:

$ cabal install --dry-run cabal-dev
Resolving dependencies...
In order, the following would be installed:
tar-0.3.2.0 (new package)
transformers-0.2.2.0 (new version)
mtl-2.0.1.0 (new version)
parsec-3.1.3 (new version)
network-2.3.1.0 (new version)
HTTP-4000.2.3 (reinstall) changes: mtl-2.1.1 - 2.0.1.0, network-2.3.0.13 -
2.3.1.0, parsec-3.1.2 - 3.1.3
cabal-dev-0.9.1 (new package)
Warning: The following packages are likely to be broken by the reinstalls:
haskell-platform-2012.2.0.0
Use --force-reinstalls if you want to install anyway.

Investigating the dependencies, it seems cabal-dev depends on
transformers  0.3, which in turn leads to an older mtl being picked,
and all the other problems.

I've only just come to this thread. There are a couple of things that
are strange. The original poster shows logs where base version changes
are listed. That's really puzzling to me. GHC usually has one version
of base installed, and that can't be changed. So why are there
several? Also, there are multiple versions of the Haskell Platform
being listed as possibly being broken. How can multiple versions of
the platform be installed at once? So something to me looks to be
strange with that installation.

There also seems to be a misconception that switching to cabal-dev
means no longer using cabal-install. I just want to clarify that this
isn't the case. The use of cabal-dev offers additional sandboxing
functionality and wraps cabal-install, but you're still using it.

The next release of cabal-install (don't know when that'll happen
though, unfortunately) will most likely have sandboxing functionality
built-in.

Cheers,
  Andres



--

Message: 2
Date: Fri, 17 Aug 2012 10:53:19 +0200
From: GiGi looee...@gmail.com
Subject: [Haskell-beginners] 99problems: different response from ghci
--runhaskell / ghc
To: beginners@haskell.org
Message-ID:
CAEp_LLwrn8njTCjOnATp8vGOOOMcw-f=wno_971alqfjwjx...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

Hi all,
trying to solve the problem 6  reverse a list
I'm getting a different behaviour from ghci / runhaskell.

main = do
  putStrLn $ concat (map show (myReverse [1,2,3]))
  -- putStrLn $ concat (map show (myReverse []))

myReverse :: [a] - [a]
myReverse [] = []
myReverse (x:xs) = go [] (x:xs)
where go :: [a] - [a] - [a]
  go curr (x:xs) | null xs  =  [x] ++ curr
  go curr (x:xs)  =  go ([x] ++ curr) xs


the second putStrLn (once uncommented) gives this error in the
runhaskell/ghc:
 Ambiguous type variable `a0' in the constraint:
  (Show a0) arising from a use of `show'
Probable fix: add a type signature that fixes these type variable(s)
In the first argument of `map', namely `show'

_but_   if I load the same source into ghci I can successfully enterrun
the command:

Prelude :reload
[1 of 1] Compiling Main ( 05.hs, interpreted )
Ok, modules loaded: Main.
*Main putStrLn $ concat (map show (myReverse []))

*Main


Then if I help the type inference changing the myReverse type declaration
to:

myReverse :: [Int] - [Int]


everything works well

So, my question is:  _where_ is the difference between ghci / runhaskell?

thx
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120817/9a35fbe3/attachment-0001.htm


Beginners Digest, Vol 50, Issue 21

2012-08-18 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  99problems: different response from ghci -- runhaskell
  / ghc (GiGi)
   2. Re:  Backtrace when a certain location in the code is
  executed (alex-hask...@copton.net)
   3. Re:  Error compiling OpenGL tutorial part 2 (Andrey Yankin)
   4. Re:  Backtrace when a certain location in the code is
  executed (Nathan H?sken)
   5. Re:  Backtrace when a certain location in the code is
  executed (Brandon Allbery)
   6. Re:  Error compiling OpenGL tutorial part 2 (Darren Grant)


--

Message: 1
Date: Fri, 17 Aug 2012 14:31:59 +0200
From: GiGi looee...@gmail.com
Subject: Re: [Haskell-beginners] 99problems: different response from
ghci -- runhaskell / ghc
To: Andres L?h and...@well-typed.com
Cc: beginners@haskell.org
Message-ID:
caep_llx+6bposhsgendewi2aksnha3jkxsxz6gfwodx7yyp...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

thanks Andres

On Fri, Aug 17, 2012 at 11:35 AM, Andres L?h and...@well-typed.com wrote:

 Hi.

  So, my question is:  _where_ is the difference between ghci / runhaskell?

 See here:


 http://www.haskell.org/ghc/docs/latest/html/users_guide/interactive-evaluation.html#extended-default-rules

 Cheers,
   Andres

 --
 Andres L?h, Haskell Consultant
 Well-Typed LLP, http://www.well-typed.com

-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120817/5f32369d/attachment-0001.htm

--

Message: 2
Date: Fri, 17 Aug 2012 14:45:06 +0200
From: alex-hask...@copton.net
Subject: Re: [Haskell-beginners] Backtrace when a certain location in
the code is executed
To: beginners@haskell.org
Message-ID: 20120817124506.GA3329@apus
Content-Type: text/plain; charset=iso-8859-1

Hi

On Thu, Aug 16, 2012 at 04:31:47PM +0200, Nathan H?sken wrote:
 I am trying to understand haskell program not written by me.
 During runtime one function is called with parameters which makes the
 function throw an error. I want to know from where the function is called.

The execution model of Haskell is completely different. Actually, code
locations are not executed. Instead, expressions are evaluated. And to
make things worse, this evaluation is performed lazyly. So there is no
stack trace as you know it from C++.

There is one nice hack, though, that often helps in such situations. The
module Debug.Trace exports a handy function 'trace :: String - a - a'.
It always returns the second argument but outputs the String to stdout
as a side effect. The hack is, that this function can be called in pure
code! (No IO type involved).

So, go to all locations in your code where you call the function is
question and wrap the calls into a trace each.

Greetings

Alex
-- next part --
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 198 bytes
Desc: Digital signature
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120817/96c7238a/attachment-0001.pgp

--

Message: 3
Date: Fri, 17 Aug 2012 18:06:22 +0400
From: Andrey Yankin yankin...@gmail.com
Subject: Re: [Haskell-beginners] Error compiling OpenGL tutorial part
2
To: Darren Grant therealklu...@gmail.com
Cc: beginners@haskell.org
Message-ID:
canxq4z2ommm-0tvosgw0n6an2q4h6vti1pq5wtlzmjqdkwr...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

Hi!

Try to group points and 7 with parentheses or put $ before points,
since points became a function at this step in tutorial.

But error message is a real mystery.
How could the actual type of mapM_ be unit?
Can somebody here explain this, please?
Is unit a monad?


2012/8/16 Darren Grant therealklu...@gmail.com:
 I am currently following the OpenGL tutorial here:

 http://www.haskell.org/haskellwiki/OpenGLTutorial2

 But in the current incarnation of Display.hs
 (http://pastebin.com/g4NekDVh) I am getting the following error:


 $ cabal install
 Resolving dependencies...
 Configuring mygl-0.1...
 Preprocessing executables for mygl-0.1...
 Building mygl-0.1...
 [3 of 5] Compiling Display  ( Display.hs,
 dist\build\mygl\mygl-tmp\Display.o )

 Display.hs:13:9:
 Couldn't match expected type `IO a0' with actual type `()'
 In the return type of a call of `mapM_'
 In a stmt of a 'do' expression:
 mapM_
   (\ (x, y, z)
  - preservingMatrix
 

Beginners Digest, Vol 50, Issue 23

2012-08-22 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  Good style on . and $ pipeline? (Carlos J. G. Duarte)
   2. Re:  Good style on . and $ pipeline? (Darren Grant)
   3. Re:  Good style on . and $ pipeline? (Brent Yorgey)
   4. Re:  Good style on . and $ pipeline? (koomi)
   5. Re:  Good style on . and $ pipeline? (Felipe Almeida Lessa)
   6.  The Holy Trinity of Functional Programming (Costello, Roger L.)
   7. Re:  Good style on . and $ pipeline? (Ozgur Akgun)


--

Message: 1
Date: Tue, 21 Aug 2012 21:34:49 +0100
From: Carlos J. G. Duarte carlos.j.g.dua...@gmail.com
Subject: [Haskell-beginners] Good style on . and $ pipeline?
To: beginners@haskell.org
Message-ID: 5033f0e9.1040...@gmail.com
Content-Type: text/plain; charset=us-ascii

An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120821/a699e877/attachment-0001.htm

--

Message: 2
Date: Tue, 21 Aug 2012 13:43:37 -0700
From: Darren Grant therealklu...@gmail.com
Subject: Re: [Haskell-beginners] Good style on . and $ pipeline?
To: Carlos J. G. Duarte carlos.j.g.dua...@gmail.com
Cc: beginners@haskell.org
Message-ID:
ca+jd6sihau_pkxw5zyh1xtj848ejkwrsw8wabjoxnuhzcwo...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

I am very new to Haskell, but what I've discovered so far is that the
application operator $ is used to improve code readability. It can
sometimes be used eliminate the need for parentheses that break
natural left-to-right reading.

Hoogle covers an example:
http://hackage.haskell.org/packages/archive/base/latest/doc/html/Prelude.html#v:-36-


Cheers!



On Tue, Aug 21, 2012 at 1:34 PM, Carlos J. G. Duarte
carlos.j.g.dua...@gmail.com wrote:
 Hi. Often I see the following pattern to build function pipelines:

 x = f1 . f2 $ fn arg

 They use the $ just before the last function call. I never got much into
 it: when to use the . or the $? I think today I figured it out:
 = . is a function composition operator: used to merge functions;
 = $ is a function application operator: used to apply a function to its
 arguments.

 If this reasoning is correct, I think the following should be a more
 adequate pattern:

 x = f1 . f2 . fn $ arg

 To merge/compose all functions first and apply the composed function to its
 parameter(s).
 Am I correct on this? Thx


 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners




--

Message: 3
Date: Tue, 21 Aug 2012 16:43:53 -0400
From: Brent Yorgey byor...@seas.upenn.edu
Subject: Re: [Haskell-beginners] Good style on . and $ pipeline?
To: beginners@haskell.org
Message-ID: 20120821204353.ga22...@seas.upenn.edu
Content-Type: text/plain; charset=us-ascii

On Tue, Aug 21, 2012 at 09:34:49PM +0100, Carlos J. G. Duarte wrote:
Hi. Often I see the following pattern to build function pipelines:
 
  x = f1 . f2 $ fn arg
 
They use the $ just before the last function call. I never got much into
it: when to use the . or the $? I think today I figured it out:
= . is a function composition operator: used to merge functions;
= $ is a function application operator: used to apply a function to its
arguments.
 
If this reasoning is correct, I think the following should be a more
adequate pattern:
 
  x = f1 . f2 . fn $ arg
 
To merge/compose all functions first and apply the composed function to
its parameter(s). 
Am I correct on this? Thx

Yes, you are absolutely correct.  But sometimes people do something
like

  f1 . f2 $ fn arg

if for some reason they are thinking of fn arg as a primitive
starting point, and then applying a pipeline of functions f2, f1 to
that.  But it is really just a different point of view.  In any case,
both (f1 . f2 . fn $ arg) and (f1 . f2 $ fn arg) are perfectly good
style.  Having more than one $, like (f1 $ f2 $ fn $ arg), is frowned
upon.

-Brent



--

Message: 4
Date: Wed, 22 Aug 2012 03:34:33 +0200
From: koomi ko...@hackerspace-bamberg.de
Subject: Re: [Haskell-beginners] Good style on . and $ pipeline?
To: beginners@haskell.org
Message-ID: 50343729.1080...@hackerspace-bamberg.de
Content-Type: text/plain; charset=ISO-8859-1

On 21.08.2012 22:43, Brent Yorgey wrote:
 Having more than one $, like (f1 $ f2 $ fn $ arg), is frowned upon.
Care to explain why this is considered bad? I don't see anything 

Beginners Digest, Vol 50, Issue 25

2012-08-23 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  Good style on . and $ pipeline? (David Johnson)
   2. Re:  The Holy Trinity of Functional Programming (Jay Sulzberger)
   3. Re:  Good style on . and $ pipeline? (Keshav Kini)


--

Message: 1
Date: Wed, 22 Aug 2012 18:18:47 -0500
From: David Johnson djohnso...@gmail.com
Subject: Re: [Haskell-beginners] Good style on . and $ pipeline?
To: Brandon Allbery allber...@gmail.com
Cc: beginners@haskell.org
Message-ID:
CAAWB79hXYVg+2uGi3KDjo2ha=avtsn2c3owowktx4wzn+ry...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

agglutinative That is one crazy word.

On Wed, Aug 22, 2012 at 10:09 AM, Brandon Allbery allber...@gmail.comwrote:

 On Tue, Aug 21, 2012 at 9:34 PM, koomi ko...@hackerspace-bamberg.dewrote:

 On 21.08.2012 22:43, Brent Yorgey wrote:
  Having more than one $, like (f1 $ f2 $ fn $ arg), is frowned upon.
 Care to explain why this is considered bad? I don't see anything wrong
 with this.


 Experientially, we see it a lot in #xmonad from beginners combining stuff
 together with a certain amont of cargo-culting (being beginners and usually
 quite unfamiliar with Haskell).

 I've been moving toward using ($) to separate logical phrases and (.)
 within the phrases, to make it easier to see which things go with which.
  Since layoutHook is rather agglutinative, this helps a lot.

 --
 brandon s allbery  allber...@gmail.com
 wandering unix systems administrator (available) (412) 475-9364 vm/sms


 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners




-- 
Cell: 1.630.740.8204
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120822/057787f0/attachment-0001.htm

--

Message: 2
Date: Wed, 22 Aug 2012 20:21:45 -0400 (EDT)
From: Jay Sulzberger j...@panix.com
Subject: Re: [Haskell-beginners] The Holy Trinity of Functional
Programming
To: beginners@haskell.org beginners@haskell.org
Message-ID: pine.neb.4.64.1208221520250.21...@panix3.panix.com
Content-Type: TEXT/PLAIN; charset=US-ASCII; format=flowed



On Wed, 22 Aug 2012, Costello, Roger L. coste...@mitre.org wrote:

 Hello Christopher,

 But do you think you could provide a
 more real world example of an application
 of the Holy Trinity ideas?

 A commonly cited real-world example that illustrates the first key idea 
 (recursive data type) is a binary tree:

 data Tree = Node String Tree Tree | Leaf

 The elements of this data type include:

   Leaf

   Node Root Leaf Leaf

   Node Root (Node Left Leaf Leaf)
   (Node Right Leaf Leaf)

   And so forth.

 Common functions on this data type include insertions, deletions, traversal.

 I am not sure if there is a use for the infinite value of this data type.

 /Roger

Let us leave aside two kind of things:

1. _|_

2. infinite things

Let us define a signature Sig to be a structure like so:

1. We have a finite set Names.

2. For each name a in Names we have a finite non-negative
integer, called the arity of a.

Note that we allow a name, say a, to have an arity of zero.  Such
names are called constants in some formalisms and distinguished
from names with an arity greater than zero.

We define a structure, sometimes called a model or an algebra
with signature Sig, to be:

1. A nonempty set S.

2. For each name a of arity n we have a function f: S^n - S,
where
a. S^n is the Cartesian product of S
b. f is everywhere defined on S^n and f is single-valued

If we call our model M then we may use this notation:

1. The ground set of M is S, which we write as Ground(M).

2. The f associated to the name a is M(a).

We now define the set of terms, which set we call Terms, over our signature:

1. Given a name a and list of terms of length n, where n is the
arity of a, t0, t1, .. t(n-1) the list a, t0, t1, ... t(n-1) is a
term.

2. Terms is the minimal set which satisfies 1.

Now, given a signature Sig, we may translate this setup into Haskell.
We do an example.  Let Sig be given as follows:

   Names is the set {a, b, c, d, e, f}.

   The arities are
a has arity 0
b has arity 0
c has arity 0
d has arity 1
e has arity 2
f has arity 5

   the set Terms over Sig is in one to one correspondence with
 

Beginners Digest, Vol 50, Issue 26

2012-08-24 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  cabal: updating a package (Obscaenvs)
   2. Re:  cabal: updating a package (Andres L?h)
   3.  How to deal with recursive/missing dependencies? (Ming Gao)


--

Message: 1
Date: Thu, 23 Aug 2012 12:39:25 +0200
From: Obscaenvs obscae...@gmail.com
Subject: [Haskell-beginners] cabal: updating a package
To: beginners@haskell.org
Message-ID: 5036085d.7050...@gmail.com
Content-Type: text/plain; charset=iso-8859-1; Format=flowed

Hi there! Excuse me, but I am a bit bewildered; should I really have to 
give cabal --force-reinstalls to upgrade yesod to the new version 
1.1.0.2? It says a lot of packages are likely to be broken, as per the 
paste http://pastebin.com/cYdZkShu.

I was under the impression I had RTFM, but maybe I have missed something?

/Fredrik
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120823/b90e3635/attachment-0001.htm

--

Message: 2
Date: Thu, 23 Aug 2012 13:17:32 +0200
From: Andres L?h andres.l...@googlemail.com
Subject: Re: [Haskell-beginners] cabal: updating a package
To: Obscaenvs obscae...@gmail.com
Cc: beginners@haskell.org
Message-ID:
CALjd_v7uDLDQs=rnkkonbucqz4k9bacdtyjcsd3nmxlspfd...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

Hi.

 Hi there! Excuse me, but I am a bit bewildered; should I really have to give
 cabal --force-reinstalls to upgrade yesod to the new version 1.1.0.2? It
 says a lot of packages are likely to be broken, as per the paste
 http://pastebin.com/cYdZkShu.

I strongly suggest not to use --upgrade-dependencies. It's probably
unavoidable to break *some* (Yesod-related) packages for a framework
with as many dependencies as Yesod has, unless you use sandboxing. But
you shouldn't go ahead installing something if packages like
bin-package-db or ghc appear among the ones that are going to be
broken. I've just tested that starting from the 2012.2.0.0 platform
and yesod-platform-1.0.4.2, a simple

$ cabal install --dry-run yesod

yields

Resolving dependencies...
In order, the following would be installed:
clientsession-0.8.0 (new version)
conduit-0.5.2.3 (new version)
attoparsec-conduit-0.5.0 (new version)
blaze-builder-conduit-0.5.0 (new version)
http-types-0.7.3 (new version)
network-conduit-0.5.0 (new version)
shakespeare-1.0.1.1 (new version)
hamlet-1.1.0.2 (new version)
shakespeare-css-1.0.1.4 (new version)
shakespeare-i18n-1.0.0.2 (reinstall) changes: shakespeare-1.0.0.2 - 1.0.1.1
shakespeare-js-1.0.0.5 (new version)
shakespeare-text-1.0.0.4 (new version)
simple-sendfile-0.2.6 (new version)
stringsearch-0.3.6.3 (new package)
tar-0.4.0.0 (new package)
unix-time-0.1.2 (new package)
fast-logger-0.2.2 (new version)
monad-logger-0.2.0 (new package)
persistent-1.0.0 (new version)
persistent-template-1.0.0 (new version)
wai-1.3.0 (new version)
wai-logger-0.2.0 (new version)
warp-1.3.0.1 (new version)
xml-types-0.3.3 (new version)
xml-conduit-1.0.3 (new version)
yaml-0.8.0.1 (new version)
yesod-routes-1.1.0 (new version)
zlib-conduit-0.5.0 (new version)
http-conduit-1.6.0 (new version)
authenticate-1.3.1 (new version)
wai-extra-1.3.0 (new version)
yesod-core-1.1.1 (new version)
yesod-json-1.1.0 (new version)
yesod-persistent-1.1.0 (new version)
yesod-form-1.1.1 (new version)
yesod-auth-1.1.1 (new version)
yesod-1.1.0.2 (new version)
Warning: The following packages are likely to be broken by the reinstalls:
yesod-platform-1.0.4.2
yesod-core-1.0.1.2
yesod-static-1.0.0.3
yesod-persistent-1.0.0.1
yesod-form-1.0.0.4
yesod-auth-1.0.2.1
yesod-1.0.1.6
yesod-json-1.0.0.1
yesod-default-1.0.1.1
Use --force-reinstalls if you want to install anyway.

for me, which looks reasonably safe to do with --force-reinstalls.

Cheers,
  Andres



--

Message: 3
Date: Thu, 23 Aug 2012 22:02:43 +0200
From: Ming Gao m...@gmx.de
Subject: [Haskell-beginners] How to deal with recursive/missing
dependencies?
To: beginners@haskell.org
Message-ID: 50368c63.6080...@gmx.de
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Hello,
I ran into some dependency issues with cabal/ghc and could not find any 
solution on the internet.
ghc-pkg check returns nothing, I suppose this is a good thing.

But ghc -v returns:

-
Glasgow Haskell Compiler, Version 7.4.1, stage 2 booted by GHC version 7.4.1
Using binary package database: 

Beginners Digest, Vol 50, Issue 28

2012-08-25 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  Difference between Monad composition and transformation
  (Song Zhang)
   2. Re:  shared files / environment / portability (Henk-Jan van Tuyl)


--

Message: 1
Date: Sat, 25 Aug 2012 09:15:20 +0100
From: Song Zhang vxan...@gmail.com
Subject: [Haskell-beginners] Difference between Monad composition and
transformation
To: beginners@haskell.org
Message-ID:
CACGMEOnGugMmzifyFR57z-mT_CFYDB5dMi3xnHsHHsi8NHC=h...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

When I use a State Monad transformer to combine with a Writer Monad
StateT s (Writer w) a. is it different from composition of State Monad and
Writer Monad. It is State s (Writer w a) ?
StateT is defined as (s - m (a, s)), so StateT s (Writer w) a can be
regarded as (s - Writer w a) , which is (s - ((a,w),s)
and on the other hand State s (Writer w a) is (s - ((a,w),s). I suppose
the are similar and if so, what is the point we still get Monad
transformers? Thanks
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120825/acd963f9/attachment-0001.htm

--

Message: 2
Date: Sat, 25 Aug 2012 10:28:17 +0200
From: Henk-Jan van Tuyl hjgt...@chello.nl
Subject: Re: [Haskell-beginners] shared files / environment /
portability
To: Haskell Beginners beginners@haskell.org, Christopher Howard
christopher.how...@frigidcode.com
Message-ID: op.wjk8hfydpz0...@zen5.arnhem.chello.nl
Content-Type: text/plain; charset=iso-8859-15; format=flowed;
delsp=yes

On Sat, 25 Aug 2012 10:08:01 +0200, Henk-Jan van Tuyl hjgt...@chello.nl  
wrote:

 On Sat, 25 Aug 2012 08:09:04 +0200, Christopher Howard  
 christopher.how...@frigidcode.com wrote:

 I'm coding a resource tracker for a game that loads images, sounds, etc.
 from files, and wondering how the program will know where the files are
 located on the installation system. (With C/C++ programs I usually had
 the build system hardcode the appropriate share/ directory into the
 config.h file.) Assuming I package for cabal distribution, what
 approaches to this problem are available to me?


 You can find an example in wxAsteroids[0], look at the main function.

Another example can be found in the FRP version of wxAsteroids[1], e.g.:
   rock= bitmap $ getDataFile rock.ico

Regards,
Henk-Jan van Tuyl

[1]  
https://github.com/HeinrichApfelmus/reactive-banana/blob/master/reactive-banana-wx/src/Asteroids.hs

-- 
http://Van.Tuyl.eu/
http://members.chello.nl/hjgtuyl/tourdemonad.html
Haskell programming
--



--

___
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 50, Issue 28
*


Beginners Digest, Vol 50, Issue 29

2012-08-26 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  Difference between Monad composition and transformation
  (Dennis Raddle)
   2. Re:  Difference between Monad composition and transformation
  (Brent Yorgey)
   3. Re:  MonadError (Nick Vanderweit)
   4. Re:  associative arrays (Nick Vanderweit)


--

Message: 1
Date: Sat, 25 Aug 2012 03:14:02 -0700
From: Dennis Raddle dennis.rad...@gmail.com
Subject: Re: [Haskell-beginners] Difference between Monad composition
and transformation
To: Haskell Beginners beginners@haskell.org
Message-ID:
CAKxLvoobf=nxutmq005ykp5iti9egat4emtmv1v_bj+ydqr...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

I'm not exactly a Haskell beginner but haven't grasped much of it yet. I
have a feeling the answer to your question has something to do with the
fact that the monad transformer library provides instances that allow the
use of, for example, get and put in any transformed monad that has a
StateT somewhere in it. Or throwError in anything that has an ErrorT in it.
In other words, you don't need to lift everything into the right level.

Okay, that's a crude way of putting it, but someone will probably come
along and clarify.
Dennis

On Sat, Aug 25, 2012 at 1:15 AM, Song Zhang vxan...@gmail.com wrote:


 When I use a State Monad transformer to combine with a Writer Monad
 StateT s (Writer w) a. is it different from composition of State Monad and
 Writer Monad. It is State s (Writer w a) ?
 StateT is defined as (s - m (a, s)), so StateT s (Writer w) a can be
 regarded as (s - Writer w a) , which is (s - ((a,w),s)
 and on the other hand State s (Writer w a) is (s - ((a,w),s). I suppose
 the are similar and if so, what is the point we still get Monad
 transformers? Thanks




 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners


-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120825/5d31f39b/attachment-0001.htm

--

Message: 2
Date: Sat, 25 Aug 2012 08:34:10 -0400
From: Brent Yorgey byor...@seas.upenn.edu
Subject: Re: [Haskell-beginners] Difference between Monad composition
and transformation
To: beginners@haskell.org
Message-ID: 20120825123410.ga15...@seas.upenn.edu
Content-Type: text/plain; charset=us-ascii

On Sat, Aug 25, 2012 at 03:14:02AM -0700, Dennis Raddle wrote:
 I'm not exactly a Haskell beginner but haven't grasped much of it yet. I
 have a feeling the answer to your question has something to do with the
 fact that the monad transformer library provides instances that allow the
 use of, for example, get and put in any transformed monad that has a
 StateT somewhere in it. Or throwError in anything that has an ErrorT in it.
 In other words, you don't need to lift everything into the right level.

Well, not really, that's a separate thing to do with type classes like
MonadState and MonadError.

To answer the OP's question, literally composing monadic types does
often give you a type similar to the transformer version.  However,
the point of composing monads is to give you a new, combined monad.
If you just use the type (State s (Writer w a)) this is just a State
computation which happens to return something of type Writer w a.
Combining such things with = does not take the Writer into account
at all.  On the other hand, StateT s (Writer w) a is a separate type
with a Monad instance that combines the effects of State and Writer.

-Brent

 
 On Sat, Aug 25, 2012 at 1:15 AM, Song Zhang vxan...@gmail.com wrote:
 
 
  When I use a State Monad transformer to combine with a Writer Monad
  StateT s (Writer w) a. is it different from composition of State Monad and
  Writer Monad. It is State s (Writer w a) ?
  StateT is defined as (s - m (a, s)), so StateT s (Writer w) a can be
  regarded as (s - Writer w a) , which is (s - ((a,w),s)
  and on the other hand State s (Writer w a) is (s - ((a,w),s). I suppose
  the are similar and if so, what is the point we still get Monad
  transformers? Thanks
 
 
 
 
  ___
  Beginners mailing list
  Beginners@haskell.org
  http://www.haskell.org/mailman/listinfo/beginners
 
 

 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners





Beginners Digest, Vol 50, Issue 30

2012-08-27 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  How to switch off a RadioMenuiItem? (Pierre Michallet)


--

Message: 1
Date: Sun, 26 Aug 2012 22:50:09 +0200
From: Pierre Michallet p.michal...@free.fr
Subject: [Haskell-beginners] How to switch off a RadioMenuiItem?
To: beginners haskell beginners@haskell.org
Message-ID: 868D84E71F204D399FF858E28799CB10@medione9995867
Content-Type: text/plain; charset=iso-8859-1

Using Glade, I have created a menu which,among other things,has 2 
radioMenuItems located in the same submenu.
Both are in the off state when the program starts.
In the following, I will refer to them as initiationCB and beginnerCB.
The expected behavior is that these 2 options are exclusive ie clicking one 
when in the OFF state will turn it ON and turn the other OFF.
In fact, the first time I click on initiationCB its associated checkbox is 
turned ON; a second click on it will not change its state.  
When beginnerCB is then clicked, it is turned ON but initiationCB is not 
turned OFF as expected, and from then on, the two items are ON and there is no 
way to  turn them OFF.
One surprising thing is that in the same menu there are 2 CheckMenuItems which, 
when clicked, change their state without any code written to obtain this 
behavior.
I would have expected the same from RadioMenuItems.
In an attempt to switch a RadioMenuItem OFF , I have added the following code:

  on initiationCB menuItemActivate
   do  checkMenuItemSetActive initiationCB True

When initiationCB is clicked (and turned ON as a consequence) the program 
blows up seeming in an infinite recursion.

The Gtk2HS tutorial (chapter 7.2) gives an example of selective choices by 
defining actions in the file called by a UIManager to get the elements of the 
user
interface and RadioActionEntry in the code.
The problem is that I could not succeed in associating an action to a menu item 
in the Glade file (as done in the tutorial), and in case of success, I don't 
know whether a
XmlGetWidget instruction would recognize it.

So the question is : is there a way to implement a solution similar to the one 
described in the tutorial using Glade instead of the UIManager approach?

Another odd thing to me is that the signal menuItemToggle is not raised when a 
radioMenuItem is clicked.

Thanks in advance for your help

p.michal...@free.fr
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120826/d03a26ba/attachment-0001.htm

--

___
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 50, Issue 30
*


Beginners Digest, Vol 50, Issue 31

2012-08-27 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  IO / State / Do Syntax (Christopher Howard)
   2. Re:  IO / State / Do Syntax (Alexander Bernauer)
   3.  Errors involving rigid skolem types (Matthew Moppett)
   4. Re:  Errors involving rigid skolem types (Matthew Moppett)
   5. Re:  Errors involving rigid skolem types (Brent Yorgey)
   6.  Are tuples really needed? (Carlos J. G. Duarte)
   7. Re:  Are tuples really needed? (Kyle Murphy)


--

Message: 1
Date: Mon, 27 Aug 2012 02:27:22 -0800
From: Christopher Howard christopher.how...@frigidcode.com
Subject: [Haskell-beginners] IO / State / Do Syntax
To: Haskell Beginners beginners@haskell.org
Message-ID: 503b4b8a.10...@frigidcode.com
Content-Type: text/plain; charset=iso-8859-1

So, I'm still working with my resource tracker idea -- keeping images
stored and organized inside a resource tracker structure that I can pass
around to functions that need them. Let's say I want a function like so:

code:

initResources :: IO ResourceTracker


The idea being that initResources loads the image files, stores them in
the resource tracker (RT) structure, and returns the RT. I know I can do
something like so:

code:

initResources = do pic1 - loadImage someimage.png -- IO function
   pic2 - loadImage someimage2.png
   -- ... and so on ...
   let rt = emptyResourceTracker in
   let rt' = storeImage rt pic1keyword pic1 in
   let rt'' = storeImage rt' pic2keyword pic2 in
   -- ... and so on, until finally: ...
   rt''


Obviously, all the let statements and apostrophes are undesirable. So,
presumably what I need is to being using the State monad, yes? (I must
confess I have only a vague understanding of the State monad, even after
reading several tutorials.) But in my initResources function, how do I
mix use of the IO and State do syntax, and still get what I want?

I think this has something to do with Monad transformers, but I'm even
less clear on how those work.

-- 
frigidcode.com
indicium.us

-- next part --
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 554 bytes
Desc: OpenPGP digital signature
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120827/605a3eda/attachment-0001.pgp

--

Message: 2
Date: Mon, 27 Aug 2012 13:49:35 +0200
From: Alexander Bernauer alex-hask...@copton.net
Subject: Re: [Haskell-beginners] IO / State / Do Syntax
To: Haskell Beginners beginners@haskell.org
Message-ID: 20120827114935.GB4253@apus
Content-Type: text/plain; charset=us-ascii

Hi

you don't need the State monad for your problem. Standard functional
composition is enough:

---8---
initResources =
   let
  images = [someimage.png, someimage2.png]
  keywords = [pic1keyword, pic2keyword]
   in do
   pics - mapM loadImage images
   let rt = foldr go emptyResourceTracker $ zip pics keywords
   -- use rt
   where
  go (pic, kw) rt = storeImage rt kw pic
---8---

Anyways, if you are interested in Monad transformers in general, go
check out http://book.realworldhaskell.org/read/monad-transformers.html

HTH

Alex
-- next part --
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 198 bytes
Desc: Digital signature
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120827/c5f15557/attachment-0001.pgp

--

Message: 3
Date: Mon, 27 Aug 2012 23:21:55 +1000
From: Matthew Moppett matthewmopp...@gmail.com
Subject: [Haskell-beginners] Errors involving rigid skolem types
To: beginners@haskell.org
Message-ID:
CAMLEjZAAhWGQWnLP=qto-kk2xqjrry5r4pzekuwmpi7y7c3...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

The following code is intended as a first step towards creating a
cyclical enumerable type, such that:
 (e.g.) [Cyc Friday .. Cyc Tuesday] would yield [Friday, Saturday,
Sunday, Monday, Tuesday]

module Cycle where

newtype Cyc a = Cyc a deriving (Eq, Ord, Bounded, Show, Read)

fromCyc :: Cyc a - a
fromCyc (Cyc a) = a

instance (Enum a, Bounded a) = Enum (Cyc a) where
fromEnum = fromEnum . fromCyc
toEnum n = Cyc x
where (x, max) = (x', maxBound) :: (a, a)
  x' = toEnum $ n `mod` ((fromEnum max) - 1)

This yields a kind of 

Beginners Digest, Vol 50, Issue 32

2012-08-28 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  Are tuples really needed? (Peter Hall)


--

Message: 1
Date: Tue, 28 Aug 2012 05:45:20 +0100
From: Peter Hall peter.h...@memorphic.com
Subject: Re: [Haskell-beginners] Are tuples really needed?
To: Carlos J. G. Duarte carlos.j.g.dua...@gmail.com
Cc: beginners@haskell.org
Message-ID:
CAA6hAk4=YzoE+1D42jOh2iYmxpp6=ZN7OkB=d-dvuhs+q8r...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

They are just syntactic sugar. You can just as easily create your own
tuple types:

data Tuple2 a b = Tuple2 a b
data Tuple3 a b c = Tuple3 a b c
data Tuple4 a b c d = Tuple4 a b c d
..etc

...except it's pretty ugly and none of the built-in Prelude functions
that use tuples will work with them (curry, uncurry, fst, snd, lookup,
zip,..).

Peter


On 28 August 2012 02:47, Carlos J. G. Duarte
carlos.j.g.dua...@gmail.com wrote:
 Sorry if this question is too insane, but I was wondering if tuples are
 really needed in Haskell. I mean, could tuples be generally replaced by
 variables unroll (f x y z) and explicit data types, or are there some things
 only possible to do via tuples?

 Thx in advance (and sorry if this looks silly).


 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners



--

___
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 50, Issue 32
*


Beginners Digest, Vol 50, Issue 33

2012-08-28 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  associative arrays (Adrien Haxaire)
   2. Re:  Are tuples really needed? (David McBride)
   3.  system call uses a different shell,or does not pick up
  the whole environment (Hong Yang)
   4. Re:  system call uses a different shell, or does not pick
  up the whole environment (Brent Yorgey)
   5. Re:  system call uses a different shell, or does not pick
  up the whole environment (Hong Yang)
   6. Re:  system call uses a different shell, or does not pick
  up the whole environment (Michael Orlitzky)


--

Message: 1
Date: Tue, 28 Aug 2012 14:29:16 +0200
From: Adrien Haxaire adr...@haxaire.org
Subject: Re: [Haskell-beginners] associative arrays
To: beginners@haskell.org
Message-ID: b1d249b8bef91dcc2b878b0e8e041...@haxaire.org
Content-Type: text/plain; charset=UTF-8; format=flowed

 On Sat, 25 Aug 2012 09:11:30 -0600, Nick Vanderweit wrote:
 I'd still recommend Data.Map, since it's a much more efficient data
 structure
 for the task.

 They are implemented as a tree, which is fine as long as you do not 
 want/need duplicates in your association list.

 They are also well documented and the extensive API will do most of 
 what you'll need. I use them a lot.


-- 
 Adrien Haxaire
 www.adrienhaxaire.org | @adrienhaxaire



--

Message: 2
Date: Tue, 28 Aug 2012 10:23:50 -0400
From: David McBride toa...@gmail.com
Subject: Re: [Haskell-beginners] Are tuples really needed?
To: Carlos J. G. Duarte carlos.j.g.dua...@gmail.com
Cc: beginners@haskell.org
Message-ID:
CAN+Tr40Bf=UOv-cP00K-1UWxy=zh9Me=qwk-hzgcs1vlkmy...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

Pattern matching makes tuples really useful.  Sometimes you just want to
return a pair of values and you don't feel like making a one off
constructor for it.

Eg: random :: (RandomGen g, Random a) = g - (a, g).  Without tuples you'd
have to have a one off type data RandomGenWithRandom g a  = RGWR g a, which
is overkill, when you just wanted two values.

On Mon, Aug 27, 2012 at 9:47 PM, Carlos J. G. Duarte 
carlos.j.g.dua...@gmail.com wrote:

 Sorry if this question is too insane, but I was wondering if tuples are
 really needed in Haskell. I mean, could tuples be generally replaced by
 variables unroll (f x y z) and explicit data types, or are there some
 things only possible to do via tuples?

 Thx in advance (and sorry if this looks silly).


 __**_
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/**mailman/listinfo/beginnershttp://www.haskell.org/mailman/listinfo/beginners

-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120828/1ad23bed/attachment-0001.htm

--

Message: 3
Date: Tue, 28 Aug 2012 09:58:16 -0500
From: Hong Yang hyang...@gmail.com
Subject: [Haskell-beginners] system call uses a different shell,  or
does not pick up the whole environment
To: beginners@haskell.org
Message-ID:
CA+_A4U5du4CTW=d+gq-hb4b7hz-vbmxlxsidukobobpbofl...@mail.gmail.com
Content-Type: text/plain; charset=utf-8

Hi,

I am trying to mimic mapM() at shell command line. I define the interface
as mapm cmd2 cmd1, so cmd2 will be run for each of the cmd1 results. $_
can be used inside cmd2 to represent the current cmd1 result.

For example, the command
mapm'cp -pr $_ destination_dir/$_'ls
copies everything under the current directory to the destination directory.

The code is as follows:

--
module Main where

import System.Environment ( getArgs )
import System.Exit
import System.IO
import System.Process
import Text.Regex
import Text.Regex.Posix

main = do
hs_argv - getArgs
if length hs_argv /= 2
  then
putStrLn wrong arguments!  exitFailure
  else do
let [cmd2, cmd1] = hs_argv
(_, hOut, hErr, _) - runInteractiveCommand cmd1
err - hGetContents hErr
hClose hErr
if null err
  then do
out - hGetContents hOut
mapM (f cmd2) (lines out)
  else
putStr err  exitFailure

f :: String - String - IO ExitCode
f cmd2 item = system cmd2'
  where cmd2' = if cmd2 =~ \\$\\_::Bool
then subRegex (mkRegex \\$\\_) cmd2 item
else cmd2
--

It works, except one issue that is bothering me.

If I issue

Beginners Digest, Vol 50, Issue 34

2012-08-28 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  system call uses a different shell, or does not pick
  up the whole environment (Matthew)
   2. Re:  system call uses a different shell, or does not pick
  up the whole environment (Hong Yang)
   3. Re:  system call uses a different shell, or does not pick
  up the whole environment (Brent Yorgey)
   4. Re:  system call uses a different shell, or does not pick
  up the whole environment (Brandon Allbery)


--

Message: 1
Date: Tue, 28 Aug 2012 08:40:09 -0700
From: Matthew wonderzom...@gmail.com
Subject: Re: [Haskell-beginners] system call uses a different shell,
or does not pick up the whole environment
To: Hong Yang hyang...@gmail.com
Cc: beginners@haskell.org
Message-ID:
cab4w-sau24kx5yrufsokeh9yntg1pizpojakjhd23-4eao1...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

Not to further discourage you from experimenting, but xargs can also
run commands in parallel. Check out the -P argument. :)

On Tue, Aug 28, 2012 at 8:19 AM, Hong Yang hyang...@gmail.com wrote:
 Hi Brent,

 Thanks for the xargs command info. I did not know it before.

 The other reason I want to play with my mapm version is eventually I want to
 make it concurrent.

 Thanks again,

 Hong


 On Tue, Aug 28, 2012 at 10:08 AM, Brent Yorgey byor...@seas.upenn.edu
 wrote:

 I do not know the solution to your problem -- dealing with shells,
 environments, etc. can be tricky.

 However, do you know about the 'xargs' command?  E.g. your example
 could be accomplished with

   ls | xargs -L 1 -I{} cp -pr {} destination_dir/{}

 -Brent

 On Tue, Aug 28, 2012 at 09:58:16AM -0500, Hong Yang wrote:
  Hi,
 
  I am trying to mimic mapM() at shell command line. I define the
  interface
  as mapm cmd2 cmd1, so cmd2 will be run for each of the cmd1 results.
  $_
  can be used inside cmd2 to represent the current cmd1 result.
 
  For example, the command
  mapm'cp -pr $_ destination_dir/$_'ls
  copies everything under the current directory to the destination
  directory.
 
  The code is as follows:
 
  --
  module Main where
 
  import System.Environment ( getArgs )
  import System.Exit
  import System.IO
  import System.Process
  import Text.Regex
  import Text.Regex.Posix
 
  main = do
  hs_argv - getArgs
  if length hs_argv /= 2
then
  putStrLn wrong arguments!  exitFailure
else do
  let [cmd2, cmd1] = hs_argv
  (_, hOut, hErr, _) - runInteractiveCommand cmd1
  err - hGetContents hErr
  hClose hErr
  if null err
then do
  out - hGetContents hOut
  mapM (f cmd2) (lines out)
else
  putStr err  exitFailure
 
  f :: String - String - IO ExitCode
  f cmd2 item = system cmd2'
where cmd2' = if cmd2 =~ \\$\\_::Bool
  then subRegex (mkRegex \\$\\_) cmd2 item
  else cmd2
  --
 
  It works, except one issue that is bothering me.
 
  If I issue
  mapm'lt $_'ls,
  I get a bunch of
  /bin/sh: lt: command not found,
  while I expect it act the same as
  mapm'ls -Alrt --color=auto $_'ls,
  because lt is aliased to ls -Alrt --color=auto.
 
  Notice /bin/sh above. My shell is actually tcsh. All the aliases are
  in
  ~/.cshrc.
 
  I tried replacing system cmd2' with
  system (source ~/.cshrc;  ++ cmd2')
  and
  system (tcsh -c  ++ 'source ~/.cshrc;  ++ cmd2' ++ '),
  but they did not solve the problem.
 
  Can someone please help me?
 
  Thanks,
 
  Hong

  ___
  Beginners mailing list
  Beginners@haskell.org
  http://www.haskell.org/mailman/listinfo/beginners


 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners



 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners




--

Message: 2
Date: Tue, 28 Aug 2012 10:49:20 -0500
From: Hong Yang hyang...@gmail.com
Subject: Re: [Haskell-beginners] system call uses a different shell,
or does not pick up the whole environment
To: Matthew wonderzom...@gmail.com
Cc: beginners@haskell.org
Message-ID:
CA+_A4U7rDXfJ-715HzH3Lk=kvb4w8CW1ovu-F=sqvkmxkab...@mail.gmail.com
Content-Type: text/plain; charset=utf-8


Beginners Digest, Vol 50, Issue 36

2012-08-29 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  IO vars (Corentin Dupont)
   2. Re:  IO vars (Mihai Maruseac)
   3. Re:  IO vars (Corentin Dupont)
   4. Re:  IO vars (Eugene Perederey)
   5. Re:  IO vars (Ozgur Akgun)


--

Message: 1
Date: Wed, 29 Aug 2012 10:58:58 +0200
From: Corentin Dupont corentin.dup...@gmail.com
Subject: [Haskell-beginners] IO vars
To: beginners@haskell.org
Message-ID:
caeyhvmo7hw5gq3m5yzovadjex7q1pny05d12gtw8mr66a2b...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

Hi all,
there is something very basic that it seems escaped me.
For example with the following program f and g have type IO () and I can
thread a value between the two using a file.
Can I do the exact same (not changing the types of f and g) without a file?*

f,g :: IO ()
**f = withFile toto WriteMode (flip hPutStr toto)
g = withFile toto ReadMode hGetLine = putStrLn
main = f  g*

Thanks and cheers,
Corentin
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120829/43c5919f/attachment-0001.htm

--

Message: 2
Date: Wed, 29 Aug 2012 11:04:06 +0200
From: Mihai Maruseac mihai.marus...@gmail.com
Subject: Re: [Haskell-beginners] IO vars
To: Corentin Dupont corentin.dup...@gmail.com
Cc: beginners@haskell.org
Message-ID:
CAOMsUMJ4cNbK4tG5Afxg41KKcGwdTXudKRrd+Tf=p0yspfk...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

On Wed, Aug 29, 2012 at 10:58 AM, Corentin Dupont
corentin.dup...@gmail.com wrote:
 Hi all,
 there is something very basic that it seems escaped me.
 For example with the following program f and g have type IO () and I can
 thread a value between the two using a file.
 Can I do the exact same (not changing the types of f and g) without a file?

 f,g :: IO ()
 f = withFile toto WriteMode (flip hPutStr toto)
 g = withFile toto ReadMode hGetLine = putStrLn
 main = f  g

Of course:

f,g :: IO ()
f = putStr Answer: 
g = print 42

Main f  g
Answer: 42

The () is threaded by , not the file content

-- 
MM



--

Message: 3
Date: Wed, 29 Aug 2012 11:21:06 +0200
From: Corentin Dupont corentin.dup...@gmail.com
Subject: Re: [Haskell-beginners] IO vars
To: Mihai Maruseac mihai.marus...@gmail.com
Cc: beginners@haskell.org
Message-ID:
CAEyhvmqxMMqKJDh8aqmLUc6+wXj2GgeWTbfw=in833bh9qu...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

Hi Mihai,
maybe the term thread in my mail is not correct.
What I mean is that a value gets stored by f and discovered by g.

*f,g :: IO ()
f = withFile toto WriteMode (flip hPutStr 42)
g = withFile toto ReadMode hGetLine = (\s - putStrLn $ Answer: ++ s)
main = f  g*

Is it possible to do the same without files (the types must remain IO())?


On Wed, Aug 29, 2012 at 11:04 AM, Mihai Maruseac
mihai.marus...@gmail.comwrote:

 On Wed, Aug 29, 2012 at 10:58 AM, Corentin Dupont
 corentin.dup...@gmail.com wrote:
  Hi all,
  there is something very basic that it seems escaped me.
  For example with the following program f and g have type IO () and I can
  thread a value between the two using a file.
  Can I do the exact same (not changing the types of f and g) without a
 file?
 
  f,g :: IO ()
  f = withFile toto WriteMode (flip hPutStr toto)
  g = withFile toto ReadMode hGetLine = putStrLn
  main = f  g

 Of course:

 f,g :: IO ()
 f = putStr Answer: 
 g = print 42

 Main f  g
 Answer: 42

 The () is threaded by , not the file content

 --
 MM

-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120829/e386960c/attachment-0001.htm

--

Message: 4
Date: Wed, 29 Aug 2012 02:28:45 -0700
From: Eugene Perederey eugene.perede...@gmail.com
Subject: Re: [Haskell-beginners] IO vars
To: Corentin Dupont corentin.dup...@gmail.com
Cc: beginners@haskell.org
Message-ID:
CAFTqo156WjDWQ1BjrtCJdJQJwsb3PNw=ivzxc3-=m0zan35...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

Of course, not.
What you do with a file is a sequence of side effects done by f, then g.
If you want to reuse the value of type IO a returned by f, your g
function would need to have type g:: a-IO ()
so that you combine the actions: f = g

On 29 August 2012 02:21, Corentin Dupont corentin.dup...@gmail.com wrote:
 Hi Mihai,
 maybe the term thread in my mail is not correct.
 What I mean is that a value 

Beginners Digest, Vol 50, Issue 37

2012-08-30 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  IO vars (Corentin Dupont)
   2. Re:  IO vars  ACID (Corentin Dupont)
   3. Re:  complex typeclass/constraint question (Brent Yorgey)
   4. Re:  IO vars (Brent Yorgey)
   5.  How to load multiple source files in GHCi? (Yang)
   6. Re:  How to load multiple source files in GHCi?
  (Alexander Bernauer)
   7. Re:  complex typeclass/constraint question (Dennis Raddle)


--

Message: 1
Date: Wed, 29 Aug 2012 12:00:50 +0200
From: Corentin Dupont corentin.dup...@gmail.com
Subject: Re: [Haskell-beginners] IO vars
To: Ozgur Akgun ozgurak...@gmail.com
Cc: beginners@haskell.org
Message-ID:
caeyhvmobyrqdkf4gseycf3axtat2u_hqlhnke2dtmzur9e4...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

Thanks Eugene and Ozgur.
I also looked on the side of IORef, but it doesn't looked to be a good
solution since we have to use unsafePerformIO.

I have a big program to modify, and I want to pass some new data to
existing functions of type IO(). I'd like to avoid changing all the
function's types down the chain... What is the best way to do that?



On Wed, Aug 29, 2012 at 11:43 AM, Ozgur Akgun ozgurak...@gmail.com wrote:

 On 29 August 2012 10:21, Corentin Dupont corentin.dup...@gmail.comwrote:

 *f,g :: IO ()
 f = withFile toto WriteMode (flip hPutStr 42)
 g = withFile toto ReadMode hGetLine = (\s - putStrLn $ Answer: ++
 s)
 main = f  g*

 Is it possible to do the same without files (the types must remain IO())?


 One can use an IORef to get a similar effect.

 import Data.IORef
 import System.IO.Unsafe

 {-# NOINLINE toto #-}
 toto :: IORef String
 toto = unsafePerformIO (newIORef )

 f,g :: IO ()
 f = writeIORef toto 42
 g = readIORef toto = (\s - putStrLn $ Answer: ++ s)

 main = f  g

 HTH,
 Ozgur

-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120829/00ede05b/attachment-0001.htm

--

Message: 2
Date: Wed, 29 Aug 2012 12:12:34 +0200
From: Corentin Dupont corentin.dup...@gmail.com
Subject: Re: [Haskell-beginners] IO vars  ACID
To: Ozgur Akgun ozgurak...@gmail.com
Cc: beginners@haskell.org
Message-ID:
CAEyhvmr8wHFxc3HZKa7P=G0V6R5UBSz=qcnr9rztfjsngvf...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

To give you more context, I have a soft using ACID state to store and
retrieve values.
For example I have a function like that:

newPlayer :: PlayerName - IO ()
newPlayer name = update $ AddPlayer name

It seems that ACID uses a global state or a file to store the events... I'd
like to suppress the ACID state for the moment, how should I do?
Change all the* IO () *types to *StateT Game IO ()*?
Indead the ACID state is started with:
c - localStartSystemState (Proxy :: Proxy Game)

Best,
C

On Wed, Aug 29, 2012 at 12:00 PM, Corentin Dupont corentin.dup...@gmail.com
 wrote:

 Thanks Eugene and Ozgur.
 I also looked on the side of IORef, but it doesn't looked to be a good
 solution since we have to use unsafePerformIO.

 I have a big program to modify, and I want to pass some new data to
 existing functions of type IO(). I'd like to avoid changing all the
 function's types down the chain... What is the best way to do that?




 On Wed, Aug 29, 2012 at 11:43 AM, Ozgur Akgun ozgurak...@gmail.comwrote:

 On 29 August 2012 10:21, Corentin Dupont corentin.dup...@gmail.comwrote:

 *f,g :: IO ()
 f = withFile toto WriteMode (flip hPutStr 42)
 g = withFile toto ReadMode hGetLine = (\s - putStrLn $ Answer: ++
 s)
 main = f  g*

 Is it possible to do the same without files (the types must remain IO())?


 One can use an IORef to get a similar effect.

 import Data.IORef
 import System.IO.Unsafe

 {-# NOINLINE toto #-}
 toto :: IORef String
 toto = unsafePerformIO (newIORef )

 f,g :: IO ()
 f = writeIORef toto 42
 g = readIORef toto = (\s - putStrLn $ Answer: ++ s)

 main = f  g

 HTH,
 Ozgur



-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120829/4949d0fa/attachment-0001.htm

--

Message: 3
Date: Wed, 29 Aug 2012 06:50:47 -0400
From: Brent Yorgey byor...@seas.upenn.edu
Subject: Re: [Haskell-beginners] complex typeclass/constraint question
To: beginners@haskell.org
Message-ID: 20120829105047.ga12...@seas.upenn.edu
Content-Type: text/plain; charset=us-ascii

On Wed, Aug 29, 2012 at 12:28:37AM -0700, 

Beginners Digest, Vol 50, Issue 39

2012-08-31 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  First version of GHC (Jonas Almstr?m Dureg?rd)
   2.  - (Patrick Redmond)
   3. Re:  - (David McBride)
   4. Re:  - (Tony Morris)
   5. Re:  - (Karl Voelker)


--

Message: 1
Date: Thu, 30 Aug 2012 17:52:21 +0200
From: Jonas Almstr?m Dureg?rd jonas.dureg...@chalmers.se
Subject: Re: [Haskell-beginners] First version of GHC
To: D?niel Arat? exitcons...@gmail.com
Cc: beginners@haskell.org
Message-ID:
cagngccbv0qdrfm7ppoa3b7c7j1nkfy+x3tebkjphgn8codz...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

According to A history of Haskell: being lazy with class, the LML
prototype was indeed used to bootstrap the first Haskell version of
GHC.

Regards,
Jonas

On 30 August 2012 17:27, Jonas Almstr?m Dureg?rd
jonas.dureg...@chalmers.se wrote:
 Hi,

 According to the GHC wikipedia page, a prototype was written in Lazy
 ML. Whether this prototype was used to bootstrap the Haskell version
 is not specified.

 Regards,
 Jonas

 On 30 August 2012 16:13, D?niel Arat? exitcons...@gmail.com wrote:
 Hi all,

 I'm curious if the first implementation of GHC was in a different
 language before its current instance could be developed.
 If yes, what language was used?
 If not, what compiler was first used to compile GHC?

 Thank you,
 Daniel

 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners



--

Message: 2
Date: Thu, 30 Aug 2012 23:00:52 -0400
From: Patrick Redmond plredm...@gmail.com
Subject: [Haskell-beginners] -
To: Haskell Beginners beginners@haskell.org
Message-ID:
cahuea4ewrehhe8clypyhoyhmjztw7pz1mvpg1db44+mn93b...@mail.gmail.com
Content-Type: text/plain; charset=UTF-8

I'm reading Learn You a Haskell for Great Good!, chapter 9, Input
and Output http://learnyouahaskell.com/input-and-output.

IO actions are given liberal coverage throughout the chapter, however
it is never mentioned whether the value-extractor syntax (-) has a
type or not.

main = do
x - getLine
putStrLn $ reverse x

In this little program, getLine has type IO String and x has type
String. This implies to me that (-) has type IO a - a. However,
GHCI chokes on :t (-) and Hoogle says it's just a syntactic element
http://www.haskell.org/haskellwiki/Keywords#.3C-.

I guess I don't have a specific question, but I was kind of expecting
it to be a function with a type because everything seems to be a
function with a type in Haskell... Thanks for listening!



--

Message: 3
Date: Thu, 30 Aug 2012 23:09:08 -0400
From: David McBride toa...@gmail.com
Subject: Re: [Haskell-beginners] -
To: Patrick Redmond plredm...@gmail.com
Cc: Haskell Beginners beginners@haskell.org
Message-ID:
can+tr40mewv0dtmrp7yq58wki8nchcx4werurjycrgkoop4...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

It is a syntatic sugar that is expanded to

getLine = \x - putStrLn $ reverse x

= is defined in the typeclass for Monad.

In general, if something is using - notation, it's type is Monad m = m a,
where m could be any of many monads, IO, Maybe, [] (lists), Parser or even
some type of yours that you made an instance of Monad, which you can do if
you would like to use that syntax.

On Thu, Aug 30, 2012 at 11:00 PM, Patrick Redmond plredm...@gmail.comwrote:

 I'm reading Learn You a Haskell for Great Good!, chapter 9, Input
 and Output http://learnyouahaskell.com/input-and-output.

 IO actions are given liberal coverage throughout the chapter, however
 it is never mentioned whether the value-extractor syntax (-) has a
 type or not.

 main = do
 x - getLine
 putStrLn $ reverse x

 In this little program, getLine has type IO String and x has type
 String. This implies to me that (-) has type IO a - a. However,
 GHCI chokes on :t (-) and Hoogle says it's just a syntactic element
 http://www.haskell.org/haskellwiki/Keywords#.3C-.

 I guess I don't have a specific question, but I was kind of expecting
 it to be a function with a type because everything seems to be a
 function with a type in Haskell... Thanks for listening!

 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners

-- next part --
An HTML attachment was scrubbed...
URL: 

Beginners Digest, Vol 50, Issue 40

2012-08-31 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  A simple function V2 (Ezequiel Hernan Di Giorgi)
   2. Re:  A simple function V2 (Gary Klindt)
   3. Re:  A simple function V2 (Gary Klindt)
   4. Re:  A simple function V2 (Ertugrul S?ylemez)
   5. Re:  A simple function V2 (Lyndon Maydwell)
   6. Re:  A simple function V2 (Brent Yorgey)
   7. Re:  A simple function V2 (Ertugrul S?ylemez)


--

Message: 1
Date: Fri, 31 Aug 2012 09:01:30 -0300
From: Ezequiel Hernan Di Giorgi hernan.digio...@gmail.com
Subject: [Haskell-beginners] A simple function V2
To: beginners@haskell.org
Message-ID:
cahrx9sxsnwd-jjh2zy5bdhfrkzr+ed-c4c1tddpi8zbjyju...@mail.gmail.com
Content-Type: text/plain; charset=utf-8

First i want to thank all the persons who responded me yesterday to help
me. Thanks! I am so happy with with your friendliness.
So i have other beginners question:

Now i want a improved version of my* intercalate*. Now i want to call a
function with two [t][t] and obtain another one which have only
even elements, even because:

   - [1,2,3,3,4][6] and the ouput [1,6]
   - [1,2,3,4][5,6,7] output [1,5,2,6,3,7]

I tried it:

*intercalate :: (Eq t) = [t] - [t] - [t]*
*intercalate (x:xs) (y:ys)*
* | xt == [] = []*
* | yt == [] = []*
* | otherwise = x : y : intercalate xs ys*
* where xt=(x:xs)*
*yt=(y:ys)*

but i get nice error

**Main intercalate [1][6]*
*[1,6*** Exception: baby.hs:(2,1)-(5,51): Non-exhaustive patterns in
function intercalate*
*
*
**Main *

(yes...the file's name is baby.hs)

Thanks in advance! (: (: (:
(: (:
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120831/5b1e2b3b/attachment-0001.htm

--

Message: 2
Date: Fri, 31 Aug 2012 14:06:02 +0200
From: Gary Klindt gary.kli...@googlemail.com
Subject: Re: [Haskell-beginners] A simple function V2
To: Ezequiel Hernan Di Giorgi hernan.digio...@gmail.com
Cc: beginners@haskell.org
Message-ID: 5040a8aa.1070...@googlemail.com
Content-Type: text/plain; charset=UTF-8; format=flowed

Hi,

you don't proof for empty lists, only for empty tails: (x:[])


On 08/31/2012 02:01 PM, Ezequiel Hernan Di Giorgi wrote:
 First i want to thank all the persons who responded me yesterday to help
 me. Thanks! I am so happy with with your friendliness.
 So i have other beginners question:

 Now i want a improved version of my* intercalate*. Now i want to call a
 function with two [t][t] and obtain another one which have only
 even elements, even because:

 - [1,2,3,3,4][6] and the ouput [1,6]
 - [1,2,3,4][5,6,7] output [1,5,2,6,3,7]

 I tried it:

 *intercalate :: (Eq t) = [t] - [t] - [t]*
 *intercalate (x:xs) (y:ys)*
 * | xt == [] = []*
 * | yt == [] = []*
 * | otherwise = x : y : intercalate xs ys*
 * where xt=(x:xs)*
 *yt=(y:ys)*

 but i get nice error

 **Main intercalate [1][6]*
 *[1,6*** Exception: baby.hs:(2,1)-(5,51): Non-exhaustive patterns in
 function intercalate*
 *
 *
 **Main *

 (yes...the file's name is baby.hs)

 Thanks in advance! (: (: (:
 (: (:



 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners




--

Message: 3
Date: Fri, 31 Aug 2012 14:16:06 +0200
From: Gary Klindt gary.kli...@googlemail.com
Subject: Re: [Haskell-beginners] A simple function V2
To: Ezequiel Hernan Di Giorgi hernan.digio...@gmail.com
Cc: beginners@haskell.org
Message-ID: 5040ab06.8080...@googlemail.com
Content-Type: text/plain; charset=UTF-8; format=flowed

my mistake, that's not right.

But you should try to use use something like this:

intercalate :: (Eq t) = [t] - [t] - [t]
intercalate _ [] = []
intercalate [] _ = []
intercalate (x:xs) (y:ys) = x : y : intercalate xs ys

with the last line, you imply that your lists have at least one element 
(through pattern matching). By the recursive call, you will enter this 
'non-exhaustive' case.

Also, instead of writing

*intercalate (x:xs) (y:ys)*
  * | xt == [] = []*
  * | yt == [] = []*
  * | otherwise = x : y : intercalate xs ys*
* where xt=(x:xs)*
  *yt=(y:ys)*

for defining xt and yt, you could write:

intercalate xt@(x:xs) yt@(y:ys)


greets



On 08/31/2012 02:06 PM, Gary Klindt wrote:
 Hi,

 you don't proof for empty lists, only for empty tails: (x:[])


 On 08/31/2012 02:01 PM, Ezequiel Hernan Di Giorgi wrote:
 First i want to thank all 

Beginners Digest, Vol 50, Issue 41

2012-08-31 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  Warp and Yesod benchmark puzzle (Lorenzo Bolla)
   2.  factorial question (KMandPJLynch)
   3. Re:  factorial question (Brandon Allbery)
   4. Re:  factorial question (Nick Vanderweit)
   5. Re:  Warp and Yesod benchmark puzzle (Bryce)
   6. Re:  A simple function V2 (Brent Yorgey)
   7.  joining lists sharing multiple type classes (Christopher Howard)
   8. Re:  A simple function V2 (Ertugrul S?ylemez)


--

Message: 1
Date: Fri, 31 Aug 2012 15:24:19 +0100
From: Lorenzo Bolla lbo...@gmail.com
Subject: [Haskell-beginners] Warp and Yesod benchmark puzzle
To: beginners@haskell.org
Message-ID:
CADjgTRwWdzvSQ1Zxmk6zkvrsGeRdAeL++CBkRm=un-3i_+m...@mail.gmail.com
Content-Type: text/plain; charset=UTF-8

Hi all,

This is a question specific to the Yesod framework, but simple enough
(I hope) to be considered a beginner question...

I am puzzled by the performance of these two very simple web-servers,
one written in Warp and another written in Yesod:

=== YESOD ===

{-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses,
TemplateHaskell #-}
import Yesod

data HelloWorld = HelloWorld

mkYesod HelloWorld [parseRoutes|
/ HomeR GET
|]

instance Yesod HelloWorld

getHomeR :: Handler RepHtml
getHomeR = defaultLayout [whamlet|$newline always
Hello World!
|]

main :: IO ()
-- main = warpDebug 3000 HelloWorld
main = warp 3000 HelloWorld

=== WARP ===

{-# LANGUAGE OverloadedStrings #-}

import Network.Wai
import Network.HTTP.Types
import Network.Wai.Handler.Warp (run)
import Data.ByteString.Lazy.Char8 ()

app :: Application
app _ = return $ responseLBS
status200
[(Content-Type, text/html)]
Hello, Warp!

main :: IO ()
main = do
putStrLn http://localhost:8080/;
run 8080 app

===

I've tested both using httperf:
$ httperf --hog --client=0/1 --server=localhost --port=3000 --uri=/
--rate=1000 --send-buffer=4096 --recv-buffer=16384 --num-conns=100
--num-calls=100 --burst-length=20

and I got very different results:

YESOD: Request rate: 4048.0 req/s (0.2 ms/req)
WARP: Request rate: 33656.2 req/s (0.0 ms/req)

Now, I understand that Yesod is expected to be slower than the raw
Warp, but I wasn't expecting a 10x slowdown, especially for such a
trivial Yesod app (no db, no auth, etc.).

[
Compilation command was: ghc -Wall -O2 --make yesod.hs
$ yesod version
yesod-core version:1.1.0
]

What is going on?

Thanks,
L.



--

Message: 2
Date: Fri, 31 Aug 2012 12:23:24 -0400
From: KMandPJLynch kmandpjly...@verizon.net
Subject: [Haskell-beginners] factorial question
To: beginners@haskell.org
Message-ID: e6b7f256-fc25-4755-a3a7-384379421...@verizon.net
Content-Type: text/plain; charset=us-ascii

Good afternoon,

I'm going thru Graham Hutton's book Programming in Haskell [and am viewing 
the associated online lectures by Erik Meijer and Graham].
I find both to be excellent.
My problem is with the following statements:

factorial'  :: Int - Int
factorial'  0= 1
factorial' (n+1) = (n+1)*factorial' n

When I load this into GHC I get the following error:

pihch01.hs:128:13: Parse error in pattern: n + 1

I'd appreciate any advice.

Good day
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120831/f6939097/attachment-0001.htm

--

Message: 3
Date: Fri, 31 Aug 2012 12:30:34 -0400
From: Brandon Allbery allber...@gmail.com
Subject: Re: [Haskell-beginners] factorial question
To: KMandPJLynch kmandpjly...@verizon.net
Cc: beginners@haskell.org
Message-ID:
CAKFCL4ULTGxrWbScJVnDUN_G1SFNX5==nbuqzvbzd4n7s77...@mail.gmail.com
Content-Type: text/plain; charset=utf-8

On Fri, Aug 31, 2012 at 12:23 PM, KMandPJLynch kmandpjly...@verizon.netwrote:

 *factorial'  :: Int - Int*
 *factorial'  0= 1*
 *factorial' (n+1) = (n+1)*factorial' n*


n+k patterns were removed from Haskell 2010.  You can re-enable them in GHC
with

{-# LANGUAGE NPlusKPatterns #-}

or

{-# LANGUAGE Haskell98 #-}

as the first line of the source file.

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120831/745221c4/attachment-0001.htm

--

Message: 4
Date: Fri, 31 

Beginners Digest, Vol 51, Issue 1

2012-09-01 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  joining lists sharing multiple type classes (Nick Vanderweit)
   2. Re:  joining lists sharing multiple type classes
  (Christopher Howard)
   3. Re:  Warp and Yesod benchmark puzzle (Felipe Almeida Lessa)
   4. Re:  Warp and Yesod benchmark puzzle (Lorenzo Bolla)
   5. Re:  Warp and Yesod benchmark puzzle (Krzysztof Skrz?tnicki)


--

Message: 1
Date: Fri, 31 Aug 2012 15:13:41 -0600
From: Nick Vanderweit nick.vanderw...@gmail.com
Subject: Re: [Haskell-beginners] joining lists sharing multiple type
classes
To: beginners@haskell.org
Message-ID: 1544399.PW3MRytGsC@euler
Content-Type: text/plain; charset=us-ascii

It's not that your syntax is off, but rather that what you're trying to do 
doesn't really make sense in the Haskell type system. Lists are by nature 
parameterized over a single type. It is possible via existential types to have 
a list over a polymorphic type like:

exists a. (Locatable a, Animation a) = a

but this is doubtfully what you want. It suffers from the fact that, for a 
given list entry, you don't actually know what its type is, and so you can't 
do anything really useful here.

So basically: you can't have two kinds of data types in a list. What you 
probably want is a data type, like:

data Object = Star ... | Asteroid ...

That is, rather than having two types that you're trying to put in a list, 
have one type with two data constructors. Then you *can* store them together, 
and write functions that operate via pattern matching on the various 
constructors. Hope that helps.


Nick

On Friday, August 31, 2012 11:34:40 AM Christopher Howard wrote:
 Hi. I've got two data structures, Star and Asteroid (eventually I'll
 make more) that both belong to the following type classes: Locatable,
 and Animation. I wanted to do something like so in part of the code:
 
 code:
 
 let stars = ... in  -- of type [Star]
 let asteroids = ... in  -- of type [Asteroid]
 let visibleObjects = do visibleObject - (stars ++ asteroids)
 ... -- prep each object for graphics system
 -- using funcs from both type classes
 ... -- feed visibleObjects to graphics system
 
 
 However, this does not work because the two lists are not automatically
 downgraded when joined together by (++). The compiler complains about
 asteroids not being of type [Star]. What is the simplest way to do
 what I am trying to do? I tried this, but I think my syntax is off:
 
 code:
 
 let visibleObjects =
   do visibleObject - ((stars :: [(Locatable a, Animation a) = a)
   ++ (asteroids :: [(Locatable a, Animation a) = a)
   )
 
 
 Compiler complains about Illegal polymorphic or qualified type.



--

Message: 2
Date: Fri, 31 Aug 2012 13:43:53 -0800
From: Christopher Howard christopher.how...@frigidcode.com
Subject: Re: [Haskell-beginners] joining lists sharing multiple type
classes
To: Haskell Beginners beginners@haskell.org
Message-ID: 50413019.1030...@frigidcode.com
Content-Type: text/plain; charset=iso-8859-1

On 08/31/2012 12:16 PM, Sergey Mironov wrote:
 Yes, you can't concat [Star] and [Asteroid] because they are of different 
 type.
 Lets assume that Animation is defined as follows
 
 class Animation a where
   feed :: GraphicSystem - a - IO () -- feeds a to graphic system
 
 and we have
 
 instance Animation Star where ...
 instance Animation Asteroid where ...
 
 than we can do
 
 game_cycle :: ([Star],[Asteroid]) - GraphicSystem - IO ()
 game_cycle world@(stars, asteroids) gs = do
 mapM (feed gs) stars
 mapM (feed gs) asteroids
 return ()
 

This would probably work, though it evades my principle inquiry, i.e.,
how to purposely downgrade multiple types which belong to the same type
classes into a single type.

 but not
 
 game_cycle :: ([Star],[Asteroid]) - GraphicSystem - IO ()
 game_cycle world@(stars, asteroids) gs = do
 mapM (feed gs) (stars ++ asteroids) -- type mismatch
 return ()
 
 If you absolutly sure, that you really need a single list of all objects,
 consider using single type for them!
 
 data WorldObject = Star ... | Asteroid ...
 
 Sergey
 

This approach is not modular... some of my types will be quite complex
and I would rather have them as their own separate data types in their
own module, rather than one monstrous type.

Looking into this some 

Beginners Digest, Vol 51, Issue 4

2012-09-03 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  (no subject) (Dennis Raddle)
   2. Re:  (no subject) (Tony Morris)


--

Message: 1
Date: Sun, 2 Sep 2012 20:32:13 -0700
From: Dennis Raddle dennis.rad...@gmail.com
Subject: [Haskell-beginners] (no subject)
To: Haskell Beginners beginners@haskell.org
Message-ID:
CAKxLvop6q48RC-YWhXS5vgGNu=zz8yz1dtvy56kj_cf_lef...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

I wanted to run the map function from Data.Map, let's call it M.map, but
inside a monad transformer stack including the Error monad.

M.map has this type:

M.map :: (Ord k) = (a - b)  - Map k a  - Map k b

However, I want to use a mapping function that has type

(Monad m) = a - m b

(i.e. errors could be thrown during the computation, a log could be
written, etc)

I wrote the following. Any comments on this way of doing things?

mapMapM :: (Monad m, Ord k) = (a - m b) - Map k a - m (Map k b)
mapMapM g mapIn = do
  let h (k,a) = do
b - g a
return (k,b)
  y - mapM h (M.toAscList mapIn)
  return $ M.fromAscList y
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120902/58b36638/attachment-0001.htm

--

Message: 2
Date: Mon, 03 Sep 2012 13:34:42 +1000
From: Tony Morris tonymor...@gmail.com
Subject: Re: [Haskell-beginners] (no subject)
To: beginners@haskell.org
Message-ID: 50442552.7080...@gmail.com
Content-Type: text/plain; charset=iso-8859-1

On 03/09/12 13:32, Dennis Raddle wrote:
 I wanted to run the map function from Data.Map, let's call it M.map,
 but inside a monad transformer stack including the Error monad.

 M.map has this type:

 M.map :: (Ord k) = (a - b)  - Map k a  - Map k b

 However, I want to use a mapping function that has type

 (Monad m) = a - m b

 (i.e. errors could be thrown during the computation, a log could be
 written, etc)

 I wrote the following. Any comments on this way of doing things?

 mapMapM :: (Monad m, Ord k) = (a - m b) - Map k a - m (Map k b)
 mapMapM g mapIn = do
   let h (k,a) = do
 b - g a
 return (k,b)
   y - mapM h (M.toAscList mapIn)
   return $ M.fromAscList y


 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners

You probably want to look at Data.Traversable#traverse.


-- 
Tony Morris
http://tmorris.net/


-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120903/901b0b52/attachment-0001.htm

--

___
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 51, Issue 4



Beginners Digest, Vol 51, Issue 5

2012-09-04 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  TagLib (linuxlinux2006)
   2.  Error Loading Stdm.lhs in Haskell platform 2012 (Iwan Awaludin)
   3. Re:  Error Loading Stdm.lhs in Haskell platform   2012
  (Eugene Perederey)
   4. Re:  programming with Error monad (Dennis Raddle)


--

Message: 1
Date: Mon, 3 Sep 2012 19:55:09 +0400
From: linuxlinux2006 linuxlinux2...@rambler.ru
Subject: [Haskell-beginners] TagLib
To: beginners@haskell.org
Message-ID: 1346687709.409781.3525.36...@saddam4.rambler.ru
Content-Type: text/plain; charset=utf-8; Format=flowed

Hello

Please tell me why this program does not work: http://hpaste.org/74171
Tags in audio file are recorded correctly, other programs see them.

Thanks for the help
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120903/9e16867d/attachment-0001.htm

--

Message: 2
Date: Tue, 4 Sep 2012 12:08:20 +0700
From: Iwan Awaludin awalu...@gmail.com
Subject: [Haskell-beginners] Error Loading Stdm.lhs in Haskell
platform 2012
To: beginners@haskell.org
Message-ID:
CAHd5so7N7nX=diyk9Sv3+553gvqmXhWqGfgcHmAh=5xr0nh...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

Dear Sir/Madam
I Installed *Haskell Platform 2012.2.0.0 for
Windowshttp://lambda.haskell.org/platform/download/2012.2.0.0/HaskellPlatform-2012.2.0.0-setup.exe
*and try to load Stdm.lhs which is downloaded from
http://www.dcs.gla.ac.uk/~jtod/discrete-mathematics/Stdm.lhs
I have this error:
stdm.lhs:1160:14: Parse error in pattern: n + 1
Failed, modules loaded: none.

Is there anything I should do to make it right?
Thank you.

-- 
Iwan Awaludin
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120904/03d69915/attachment-0001.htm

--

Message: 3
Date: Mon, 3 Sep 2012 23:46:49 -0700
From: Eugene Perederey eugene.perede...@gmail.com
Subject: Re: [Haskell-beginners] Error Loading Stdm.lhs in Haskell
platform2012
To: Iwan Awaludin awalu...@gmail.com
Cc: beginners@haskell.org
Message-ID:
caftqo17cq4-h_ygjdqzfcfgsuh4eykn40ytge3x5kvxes+v...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

What version of ghc are you using?
In recent versions ghc doesn't support pattern matching of expressions
like (n+1).
You can rewrite that factorial function as
 factorial n = n * factorial (n-1)
instead.

best,
Eugene

On 3 September 2012 22:08, Iwan Awaludin awalu...@gmail.com wrote:
 Dear Sir/Madam
 I Installed Haskell Platform 2012.2.0.0 for Windows and try to load Stdm.lhs
 which is downloaded from
 http://www.dcs.gla.ac.uk/~jtod/discrete-mathematics/Stdm.lhs
 I have this error:
 stdm.lhs:1160:14: Parse error in pattern: n + 1
 Failed, modules loaded: none.

 Is there anything I should do to make it right?
 Thank you.

 --
 Iwan Awaludin




 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners




--

Message: 4
Date: Mon, 3 Sep 2012 23:56:55 -0700
From: Dennis Raddle dennis.rad...@gmail.com
Subject: Re: [Haskell-beginners] programming with Error monad
To: Haskell Beginners beginners@haskell.org
Message-ID:
cakxlvor+oxe9bzrte9lxhar7v6larrfsmrdeyekkac1v6a6...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

No one replied to this, but I think I figured out why, when I am using the
Error monad, that every statement in a do construct runs at least part way,
whether or not its data is needed. The final output is a Left or Right
value -- and because a Left anywhere can short-circuit the compuation that
follows, there is no way for the program to decide on a final Left/Right
output without running each computation (or at least up to the point where
it's not a Left).

On Sat, Sep 1, 2012 at 12:59 PM, Dennis Raddle dennis.rad...@gmail.comwrote:

 I recently completed a large project and started another one. The first
 project was about processing music, in particular taking MusicXML and/or
 Sibelius files (Sibelius is a music notation program) and producing MIDI
 files according to the specifications I wanted.

 The second project is about algorithmic music composition.

 To handle errors in the first project, I used throw to throw exceptions.

 Now I am using the Error monad... 

Beginners Digest, Vol 51, Issue 6

2012-09-04 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  space leak processing multiple compressed files (Ian Knopke)
   2.  monads / do syntax (Christopher Howard)
   3. Re:  monads / do syntax (Ozgur Akgun)
   4. Re:  space leak processing multiple compressedfiles
  (Lorenzo Bolla)
   5. Re:  space leak processing multiple compressedfiles (Ian Knopke)
   6. Re:  space leak processing multiple compressedfiles
  (Benjamin Edwards)
   7. Re:  space leak processing multiple compressed files
  (Michael Orlitzky)


--

Message: 1
Date: Tue, 4 Sep 2012 11:00:48 +0100
From: Ian Knopke ian.kno...@gmail.com
Subject: [Haskell-beginners] space leak processing multiple compressed
files
To: beginners@haskell.org
Message-ID:
CAC+f4w=PL_8CbaqjGtPy_bEHOUnCRfLUCDzC6a=6+0tzdtk...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

Hi everyone,

I have a collection of bzipped files. Each file has a different number
of items per line, with a separator between them. What I want to do is
count the items in each file. I'm trying to read the files lazily but
I seem to be running out of memory. I'm assuming I'm holding onto
resources longer than I need to. Does anyone have any advice on how to
improve this?

Here's the basic program, slightly sanitized:

main = do

-- get a list of file names
filelist - getFileList testsetdir

-- process each compressed file
files - mapM (\x - do
thisfile - B.readFile x
return (Z.decompress thisfile)
) filelist


display $ processEntries files


putStrLn finished

-- processEntries
-- processEntries is defined elsewhere, but basically does some string
processing per line,
-- counts the number of resulting elements and sums them per file
processEntries :: [B.ByteString] - Int
processEntries xs = foldl' (\x y - x + processEntries (B.lines y)) 0 xs

-- display a field that returns a number
display :: Int - IO ()
display = putStrLn . show



--

Message: 2
Date: Tue, 04 Sep 2012 04:03:28 -0800
From: Christopher Howard christopher.how...@frigidcode.com
Subject: [Haskell-beginners] monads / do syntax
To: Haskell Beginners beginners@haskell.org
Message-ID: 5045ee10.3040...@frigidcode.com
Content-Type: text/plain; charset=iso-8859-1

What does the following do expression translate into? (I.e., using =
operator and lambda functions.)

code:

h = do a - (return 1 :: IO Integer)
   b - (return 2)
   return (a + b + 1)


-- 
frigidcode.com
indicium.us

-- next part --
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 554 bytes
Desc: OpenPGP digital signature
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120904/b3bac86d/attachment-0001.pgp

--

Message: 3
Date: Tue, 4 Sep 2012 13:10:18 +0100
From: Ozgur Akgun ozgurak...@gmail.com
Subject: Re: [Haskell-beginners] monads / do syntax
To: Christopher Howard christopher.how...@frigidcode.com
Cc: Haskell Beginners beginners@haskell.org
Message-ID:
calzazpdcx_cgg1xkoezprbppb9xf7vhh5-qsu9w0owdueki...@mail.gmail.com
Content-Type: text/plain; charset=utf-8

Hi,

On 4 September 2012 13:03, Christopher Howard 
christopher.how...@frigidcode.com wrote:

 h = do a - (return 1 :: IO Integer)
b - (return 2)
return (a + b + 1)


h =
(return 1 :: IO Integer) = \ a -
(return 2) = \ b -
return (a + b + 1)

HTH,
Ozgur
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120904/faefb460/attachment-0001.htm

--

Message: 4
Date: Tue, 4 Sep 2012 13:55:38 +0100
From: Lorenzo Bolla lbo...@gmail.com
Subject: Re: [Haskell-beginners] space leak processing multiple
compressed  files
To: Ian Knopke ian.kno...@gmail.com
Cc: beginners@haskell.org
Message-ID:
cadjgtry+rh+nkon4jwnmtdt_b5nmypw-kqpkuwfdxscerxn...@mail.gmail.com
Content-Type: text/plain; charset=UTF-8

On Tue, Sep 4, 2012 at 11:00 AM, Ian Knopke ian.kno...@gmail.com wrote:
 main = do

 -- get a list of file names
 filelist - getFileList testsetdir

 -- process each compressed file
 files - mapM (\x - do
 thisfile - B.readFile x
 return (Z.decompress thisfile)

Beginners Digest, Vol 51, Issue 7

2012-09-04 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  monads / do syntax (Thiago Negri)
   2. Re:  Error Loading Stdm.lhs in Haskell platform   2012
  (Stephen Tetley)
   3.  Thread Blocking (mukesh tiwari)
   4. Re:  Thread Blocking (Eugene Perederey)
   5. Re:  Thread Blocking (mukesh tiwari)
   6. Re:  Thread Blocking (Eugene Perederey)


--

Message: 1
Date: Tue, 4 Sep 2012 13:38:42 -0300
From: Thiago Negri evoh...@gmail.com
Subject: Re: [Haskell-beginners] monads / do syntax
To: Christopher Howard christopher.how...@frigidcode.com
Cc: Haskell Beginners beginners@haskell.org
Message-ID:
CABLneZvsjXsVTinNrhJG9hUkW_01d3-O=jeuqpjashs-ccp...@mail.gmail.com
Content-Type: text/plain; charset=UTF-8

Go line by line, except the last one:
a) When you see the pattern a - b, just swap it with b = \s -;
b) When you see the pattern b, put a  at the end of the line.

In your case:

| h = (return 1 :: IO Integer) = \a -
|return 2 = \b -
|return (a + b + 1)


An example when you have a line without an assignment (-), this:

| h = do a - (return 1 :: IO Integer)
|b - (return 2)
|putStrLn Hello, world!
|return (a + b + 1)

Turns into:

| h = (return 1 :: IO Integer) = \a -
|return 2 = \b -
|putStrLn Hello, world! 
|return (a + b + 1)


2012/9/4 Christopher Howard christopher.how...@frigidcode.com:
 What does the following do expression translate into? (I.e., using =
 operator and lambda functions.)

 code:
 
 h = do a - (return 1 :: IO Integer)
b - (return 2)
return (a + b + 1)
 



--

Message: 2
Date: Tue, 4 Sep 2012 17:40:45 +0100
From: Stephen Tetley stephen.tet...@gmail.com
Subject: Re: [Haskell-beginners] Error Loading Stdm.lhs in Haskell
platform2012
To: Iwan Awaludin awalu...@gmail.com
Cc: beginners@haskell.org
Message-ID:
CAB2TPRDoOVD_M4Br-=vfgdggakw0p3xukh1qtyrtt4h2pmc...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

The code for the book is written in Haskell '98, but recent versions
of GHC default to Haskell2010.

A salient difference between H98 and H2012 is the removed of n + k
patterns which generates the error you are seeing.

I can't find the exact command to use in the GHC docs to enable H98,
but you could try the following old flag which disables GHCs
extensions:

 ghci  -fno-glasgow-exts



--

Message: 3
Date: Wed, 5 Sep 2012 00:24:30 +0530
From: mukesh tiwari mukeshtiwari.ii...@gmail.com
Subject: [Haskell-beginners] Thread Blocking
To: beginners@haskell.org
Message-ID:
CAFHZvE9pKn7_EM9t=x3sfay3oqvnmrmk_7xe9ro9jswbqpn...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

Hello All
I was going trough Real World Haskell and it says If we try to put a value
into an MVar that is already full, our thread is put to sleep until another
thread takes the value out. I wrote a simple code to block main

import Data.List
import Control.Concurrent

fun m = do
   putMVar m 10
   return ()


main = do
  m - newEmptyMVar
  forkIO $ fun m
  putMVar m 10
  return ()

What I am expecting that main should be blocked at least couple of times
but its behaving more deterministically.
[mukesh.tiwari@ Programming]$ ghc-7.4.1 -threaded -fforce-recomp
Concurrent.hs
[1 of 1] Compiling Main ( Concurrent.hs, Concurrent.o )
Linking Concurrent ...
[mukesh.tiwari@ Programming]$ ./Concurrent  +RTS -N2
[mukesh.tiwari@ Programming]$ ./Concurrent  +RTS -N2
[mukesh.tiwari@ Programming]$ ./Concurrent  +RTS -N2
[mukesh.tiwari@ Programming]$ ./Concurrent  +RTS -N2
[mukesh.tiwari@ Programming]$ ./Concurrent  +RTS -N2
[mukesh.tiwari@ Programming]$ ./Concurrent  +RTS -N2
[mukesh.tiwari@ Programming]$ ./Concurrent  +RTS -N2
[mukesh.tiwari@ Programming]$ ./Concurrent  +RTS -N2
[mukesh.tiwari@ Programming]$ ./Concurrent  +RTS -N2
[mukesh.tiwari@ Programming]$ ./Concurrent  +RTS -N2
[mukesh.tiwari@ Programming]$ ./Concurrent  +RTS -N2
[mukesh.tiwari@ Programming]$ ./Concurrent  +RTS -N2
[mukesh.tiwari@ Programming]$ ./Concurrent  +RTS -N2
[mukesh.tiwari@ Programming]$ ./Concurrent  +RTS -N2
[mukesh.tiwari@ Programming]$ ./Concurrent  +RTS -N2
[mukesh.tiwari@ Programming]$

I am expecting to get thread blocked indefinitely on MVar at least half the
time. Could some one please tell me why this deterministic behavior ?
Regards
Mukesh Tiwari
-- next part --
An HTML attachment was scrubbed...
URL: 

Beginners Digest, Vol 51, Issue 8

2012-09-04 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  Thread Blocking (Eugene Perederey)
   2.  XML output (Torsten Otto)
   3. Re:  Error Loading Stdm.lhs in Haskell platform   2012
  (Stephen Tetley)
   4. Re:  Error Loading Stdm.lhs in Haskell platform 2012
  (Carlos J. G. Duarte)
   5. Re:  Thread Blocking (Dean Herington  Elizabeth Lacey)
   6. Re:  XML output (Manfred Lotz)


--

Message: 1
Date: Tue, 4 Sep 2012 12:30:06 -0700
From: Eugene Perederey eugene.perede...@gmail.com
Subject: Re: [Haskell-beginners] Thread Blocking
To: mukesh tiwari mukeshtiwari.ii...@gmail.com
Cc: beginners@haskell.org
Message-ID:
CAFTqo159L-jcLhCBPREP_Gdq5uCuX7iP1A0OGPaPYftM=ms...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

Well, not 50/50 but not deterministically -- I've caught
fun1-main1-fun2 sequence,
main1-fun1-main2 is much more often.
Since you are using -threaded, the Haskell threads are running on top
of the OS threads, so I guess it depends on the OS scheduler.

On 4 September 2012 12:27, Eugene Perederey eugene.perede...@gmail.com wrote:
 I added a few prints to your code

 fun m = do
   putStrLn fun1
   putMVar m 10
   putStrLn fun2


 main = do
   m - newEmptyMVar
   forkIO $ fun m
   putStrLn main1
   putMVar m 10
   putStrLn main2

 It works 50/50 for me in Mac OS X 10.6.8.

 On 4 September 2012 12:16, mukesh tiwari mukeshtiwari.ii...@gmail.com wrote:
 Hi Eugene
 Thank you for reply.

 On Wed, Sep 5, 2012 at 12:32 AM, Eugene Perederey
 eugene.perede...@gmail.com wrote:

 Why do you think main should block more than once?
 I see only two possible scenarios: the fun thread puts to mvar first
 thus blocking main,


 So at least in this case I should get thread blocked indefinitely in an MVar
 operation


 or 10 is put into mvar in main, blocking the other thread indefinitely.


 or main will execute and fun thread will die. There are 50 - 50 chance for
 this ( assuming both are equally likely ). I did some modification in my
 code and Now I am  consistently getting Concurrent: thread blocked
 indefinitely in an MVar operation


 import Data.List
 import Control.Concurrent

 fun m = do
putMVar m 10
return ()


 main = do
   m - newEmptyMVar
   forkIO $ fun m
   putStrLn I am inside main

   putMVar m 10
   return ()

 [mukesh.tiwari@ Programming]$ ghc-7.4.1 -threaded -fforce-recomp
 Concurrent.hs
 [1 of 1] Compiling Main ( Concurrent.hs, Concurrent.o )
 Linking Concurrent ...
 [mukesh.tiwari@ Programming]$ ./Concurrent  +RTS -N2
 I am inside main
 Concurrent: thread blocked indefinitely in an MVar operation

 [mukesh.tiwari@ Programming]$ ./Concurrent  +RTS -N2
 I am inside main
 Concurrent: thread blocked indefinitely in an MVar operation

 [mukesh.tiwari@ Programming]$ ./Concurrent  +RTS -N2
 I am inside main
 Concurrent: thread blocked indefinitely in an MVar operation

 [mukesh.tiwari@ Programming]$ ./Concurrent  +RTS -N2
 I am inside main
 Concurrent: thread blocked indefinitely in an MVar operation

 [mukesh.tiwari@ Programming]$ ./Concurrent  +RTS -N2
 I am inside main
 Concurrent: thread blocked indefinitely in an MVar operation

 My question is why the outcome in first case is deterministic. Every time
 the code executing  ( at least half the time main thread should be blocked )
 .

 Regards
 Mukesh Tiwari



 On 4 September 2012 11:54, mukesh tiwari mukeshtiwari.ii...@gmail.com
 wrote:
  Hello All
  I was going trough Real World Haskell and it says If we try to put a
  value
  into an MVar that is already full, our thread is put to sleep until
  another
  thread takes the value out. I wrote a simple code to block main
 
  import Data.List
  import Control.Concurrent
 
  fun m = do
 putMVar m 10
 return ()
 
 
  main = do
m - newEmptyMVar
forkIO $ fun m
putMVar m 10
return ()
 
  What I am expecting that main should be blocked at least couple of times
  but its behaving more deterministically.
  [mukesh.tiwari@ Programming]$ ghc-7.4.1 -threaded -fforce-recomp
  Concurrent.hs
  [1 of 1] Compiling Main ( Concurrent.hs, Concurrent.o )
  Linking Concurrent ...
  [mukesh.tiwari@ Programming]$ ./Concurrent  +RTS -N2
  [mukesh.tiwari@ Programming]$ ./Concurrent  +RTS -N2
  [mukesh.tiwari@ Programming]$ ./Concurrent  +RTS -N2
  [mukesh.tiwari@ Programming]$ ./Concurrent  +RTS -N2
  [mukesh.tiwari@ Programming]$ ./Concurrent  +RTS -N2
  [mukesh.tiwari@ Programming]$ ./Concurrent  +RTS -N2
  [mukesh.tiwari@ 

Beginners Digest, Vol 51, Issue 9

2012-09-06 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  unfamiliar syntax in class definition (Christopher Howard)
   2. Re:  unfamiliar syntax in class definition (Rodrigo Ribeiro)
   3.  Haskell seems setup for iterative numerics; i.e. a standard
  example is Newton's method where lazy evaluation ... (KC)
   4. Re:  [Haskell-cafe] Haskell seems setup for iterative
  numerics; i.e. a standard example is Newton's method where lazy
  evaluation ... (KC)
   5. Re:  Error Loading Stdm.lhs in Haskell platform   2012
  (Iwan Awaludin)


--

Message: 1
Date: Wed, 05 Sep 2012 04:13:25 -0800
From: Christopher Howard christopher.how...@frigidcode.com
Subject: [Haskell-beginners] unfamiliar syntax in class definition
To: Haskell Beginners beginners@haskell.org
Message-ID: 504741e5.50...@frigidcode.com
Content-Type: text/plain; charset=iso-8859-1

The MonadState class is defined as:

quote:

class Monad m = MonadState s m | m - s where
...etc...


Please explain the part | m - s, that is, the use of the pipe symbol
and the right arrow symbol which follow MonadState s m.


-- 
frigidcode.com
indicium.us

-- next part --
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 554 bytes
Desc: OpenPGP digital signature
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120905/0d54c145/attachment-0001.pgp

--

Message: 2
Date: Wed, 5 Sep 2012 09:11:22 -0300
From: Rodrigo Ribeiro rodrigogribe...@gmail.com
Subject: Re: [Haskell-beginners] unfamiliar syntax in class definition
To: Christopher Howard christopher.how...@frigidcode.com
Cc: Haskell Beginners beginners@haskell.org
Message-ID:
caoviy-pgpzely4tbgyhmytqoajqbpqnnzlwvm6bdvk225v6...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

Hi,

This is a functional dependency:

http://www.haskell.org/haskellwiki/Functional_dependencies

[ ]s

Rodrigo

On Wed, Sep 5, 2012 at 9:13 AM, Christopher Howard 
christopher.how...@frigidcode.com wrote:

 The MonadState class is defined as:

 quote:
 
 class Monad m = MonadState s m | m - s where
 ...etc...
 

 Please explain the part | m - s, that is, the use of the pipe symbol
 and the right arrow symbol which follow MonadState s m.


 --
 frigidcode.com
 indicium.us


 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners


-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120905/8b454fa2/attachment-0001.htm

--

Message: 3
Date: Wed, 5 Sep 2012 09:46:45 -0700
From: KC kc1...@gmail.com
Subject: [Haskell-beginners] Haskell seems setup for iterative
numerics; i.e. a standard example is Newton's method where lazy
evaluation ...
To: haskell-cafe haskell-c...@haskell.org, beginners@haskell.org
Message-ID:
camlkxyk0d-vr75yrfn-xrnyw7447bnr11o1u4gagjpsikdq...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

separates control from computation.

It seems as if Haskell would be better for iterative matrix methods
rather than direct calculation.

-- 
--
Regards,
KC



--

Message: 4
Date: Wed, 5 Sep 2012 13:10:52 -0700
From: KC kc1...@gmail.com
Subject: Re: [Haskell-beginners] [Haskell-cafe] Haskell seems setup
for iterative numerics; i.e. a standard example is Newton's method
where lazy evaluation ...
To: Carter Schonwald carter.schonw...@gmail.com
Cc: beginners@haskell.org, haskell-cafe haskell-c...@haskell.org
Message-ID:
camlkxymrv9wyboo4orsgqhlqw-x_jm1ptcp6txmelqc43io...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

The REPA package/library doesn't have LU factorization, eigenvalues, etc.


On Wed, Sep 5, 2012 at 12:59 PM, Carter Schonwald
carter.schonw...@gmail.com wrote:
 Hello KC,
 you should check out the Repa library then and see how it works for you.
 Cheers
 -Carter

 On Wed, Sep 5, 2012 at 12:46 PM, KC kc1...@gmail.com wrote:

 separates control from computation.

 It seems as if Haskell would be better for iterative matrix methods
 rather than direct calculation.

 --
 --
 Regards,
 KC

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





-- 

Beginners Digest, Vol 51, Issue 10

2012-09-07 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  splitAt and negative values (Stayvoid)
   2. Re:  splitAt and negative values (Brent Yorgey)
   3. Re:  splitAt and negative values (Stephen Tetley)
   4. Re:  splitAt and negative values (Tom Murphy)
   5. Re:  splitAt and negative values (Brandon Allbery)
   6.  Who discovered the fold operation? (Costello, Roger L.)
   7. Re:  Who discovered the fold operation? (Tony Morris)


--

Message: 1
Date: Thu, 6 Sep 2012 21:24:13 +0400
From: Stayvoid stayv...@gmail.com
Subject: [Haskell-beginners] splitAt and negative values
To: beginners@haskell.org
Message-ID:
CAK5fS_GfyY7yog82droYJxY7fdi=ehcxvu+z8xg17y7dma3...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

Hello,

Could you explain this behaviour?

 splitAt (-1) Foobar
(,Foobar)
 splitAt (-100) Foobar
(,Foobar)

I don't understand why splitAt (-1) Foobar doesn't output this:
(r, Fooba)
or this:
(, Fooba)

How does it work?

Python's list slicing looks similar, but results for negative values differ:
 a = Foobar
 a[:-1]
 'Fooba'

Thanks



--

Message: 2
Date: Thu, 6 Sep 2012 17:12:47 -0400
From: Brent Yorgey byor...@seas.upenn.edu
Subject: Re: [Haskell-beginners] splitAt and negative values
To: beginners@haskell.org
Message-ID: 20120906211247.ga18...@seas.upenn.edu
Content-Type: text/plain; charset=us-ascii

On Thu, Sep 06, 2012 at 09:24:13PM +0400, Stayvoid wrote:
 Hello,
 
 Could you explain this behaviour?
 
  splitAt (-1) Foobar
 (,Foobar)
  splitAt (-100) Foobar
 (,Foobar)

That is simply how splitAt is defined.  It treats negative values as
if they were 0.

If you are looking for an explanation of *why* this behavior was
chosen, it is probably because Haskell lists are really *singly-linked
lists*, not arrays.  Taking something off the end of a list takes O(n)
time and requires making a copy of the entire list.  So it wouldn't be
a good idea to encourage it.

If you really need this sort of functionality often then perhaps you
should be using a different type, such as Data.Text, which has
functions for doing things efficiently at the end of some text:

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

-Brent



--

Message: 3
Date: Thu, 6 Sep 2012 22:14:09 +0100
From: Stephen Tetley stephen.tet...@gmail.com
Subject: Re: [Haskell-beginners] splitAt and negative values
To: Stayvoid stayv...@gmail.com
Cc: beginners@haskell.org
Message-ID:
cab2tprdm3xd9o0a2d0s3wxctte+fwhhccbjzra0bti2tvrn...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

In Haskell positional list functions treat negative values as zero:

 take (-1) abc


 drop (-2) xyz

xyz

So, its idiomatic of splitAt to follow Haskell's precedent rather than Python's.



--

Message: 4
Date: Thu, 6 Sep 2012 19:48:46 -0400
From: Tom Murphy amin...@gmail.com
Subject: Re: [Haskell-beginners] splitAt and negative values
To: Stayvoid stayv...@gmail.com
Cc: beginners@haskell.org
Message-ID:
cao9q0tvrm9ur3_m2ngsjzd4tctwas31nigdwxa8ejyht2s_...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

One problem you might run into is:

a = 4
b = 5
splitAt (a - b) [1..]

If you don't know what a or b are beforehand, you might be opening up a can
of uncomputable worms.

Tom
On Sep 6, 2012 1:25 PM, Stayvoid stayv...@gmail.com wrote:

 Hello,

 Could you explain this behaviour?

  splitAt (-1) Foobar
 (,Foobar)
  splitAt (-100) Foobar
 (,Foobar)

 I don't understand why splitAt (-1) Foobar doesn't output this:
 (r, Fooba)
 or this:
 (, Fooba)

 How does it work?

 Python's list slicing looks similar, but results for negative values
 differ:
  a = Foobar
  a[:-1]
  'Fooba'

 Thanks

 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners

-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120906/6770f82a/attachment-0001.htm

--

Message: 5
Date: Thu, 6 Sep 2012 22:06:57 -0400
From: Brandon Allbery allber...@gmail.com
Subject: Re: [Haskell-beginners] splitAt and negative values
To: Stayvoid stayv...@gmail.com
Cc: beginners@haskell.org
Message-ID:
CAKFCL4Vad0MRj73gkB98Vrp46N7JUFg8akNk8Z-CP+cGKV1=g...@mail.gmail.com
Content-Type: text/plain; charset=utf-8

On Thu, Sep 6, 2012 at 1:24 PM, Stayvoid 

Beginners Digest, Vol 51, Issue 14

2012-09-10 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  Data.Char: isAlpha vs. isLetter (Stayvoid)
   2. Re:  sometimes Haskell isn't what you want (Angelos Sphyris)
   3. Re:  Data.Char: isAlpha vs. isLetter (Brandon Allbery)
   4. Re:  sometimes Haskell isn't what you want (Nick Vanderweit)
   5. Re:  sometimes Haskell isn't what you want (Jay Sulzberger)
   6.  Who discovered map reduce? (Bryce)
   7. Re:  Who discovered map reduce? (Nick Vanderweit)
   8. Re:  Who discovered map reduce? (Rustom Mody)


--

Message: 1
Date: Mon, 10 Sep 2012 23:09:20 +0400
From: Stayvoid stayv...@gmail.com
Subject: [Haskell-beginners] Data.Char: isAlpha vs. isLetter
To: beginners beginners@haskell.org
Message-ID:
CAK5fS_HdL+EKx45HmaujtCV2z=eer3obdpj15zu5nczxs-x...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

Hi,

What's the reason to have both isAlpha and isLetter?
Looks like it's just an alias.
I don't understand the purpose.
Could you explain?

Thanks



--

Message: 2
Date: Mon, 10 Sep 2012 22:24:44 +0300
From: Angelos Sphyris knightofmathemat...@hotmail.com
Subject: Re: [Haskell-beginners] sometimes Haskell isn't what you want
To: dennis.rad...@gmail.com, beginners@haskell.org
Message-ID: snt107-w90edf53f85dd9dc7ca35fa5...@phx.gbl
Content-Type: text/plain; charset=iso-8859-7


Well, at least you now know that the language exists and you have some idea of 
where its associated resources (libraries, tutorials...) are located, so that 
you can take it up again if the need arises in the future...
 
Angelos
 



Date: Sun, 9 Sep 2012 01:10:14 -0700
From: dennis.rad...@gmail.com
To: beginners@haskell.org
Subject: [Haskell-beginners] sometimes Haskell isn't what you want

Sadly, I've decided Haskell is not the right language for my current project. 
Python is better. I need to hack together data, and strict typing is getting in 
the way. Most of my algorithms are better served with imperative/mutable-data. 
I learned a lot about Haskell trying to do it, but my knowledge of the language 
is not quiet good enough and I feel like I'm fighting the language. Python is 
better. For now.


___ Beginners mailing list 
Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners 
   
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120910/efedfe73/attachment-0001.htm

--

Message: 3
Date: Mon, 10 Sep 2012 15:31:26 -0400
From: Brandon Allbery allber...@gmail.com
Subject: Re: [Haskell-beginners] Data.Char: isAlpha vs. isLetter
To: Stayvoid stayv...@gmail.com
Cc: beginners beginners@haskell.org
Message-ID:
cakfcl4v3q4pd3kwbr94ew5cgzhk+lsxxuic-vf1vz-b-pzt...@mail.gmail.com
Content-Type: text/plain; charset=utf-8

On Mon, Sep 10, 2012 at 3:09 PM, Stayvoid stayv...@gmail.com wrote:

 What's the reason to have both isAlpha and isLetter?


Probably an alias for backward compatibility; isAlpha is C-style ctype.h
stuff, which was ASCII only, whereas isLetter is Unicode style.

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120910/576612e2/attachment-0001.htm

--

Message: 4
Date: Mon, 10 Sep 2012 14:16:02 -0700 (PDT)
From: Nick Vanderweit nick.vanderw...@gmail.com
Subject: Re: [Haskell-beginners] sometimes Haskell isn't what you want
To: beginners@haskell.org
Message-ID: 2776518.ja9fi27GRP@euler
Content-Type: text/plain; charset=us-ascii

I agree with this. Often it seems that Haskell takes longer to write, but I 
think this is because it makes you work harder than other languages before it 
compiles successfully. The tradeoff here is that you wind up with fewer runtime 
errors, which are more frustrating than compiler errors.

A Haskell program is a proof of its own type. Writing proofs is a challenging 
task. Whether you want to incur this overhead is, of course, up to you as a 
programmer.


Nick

On Monday, September 10, 2012 03:28:45 PM damodar kulkarni wrote:
  ... strict typing is getting in the way
 
 When Haskell's strict typing seems to get in your way, chances are more
 that you are heading 

Beginners Digest, Vol 51, Issue 15

2012-09-11 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  Data.Char: isAlpha vs. isLetter (Joey Hess)
   2. Re:  Data.Char: isAlpha vs. isLetter (Stayvoid)


--

Message: 1
Date: Tue, 11 Sep 2012 01:49:19 -0400
From: Joey Hess j...@kitenet.net
Subject: Re: [Haskell-beginners] Data.Char: isAlpha vs. isLetter
To: beginners beginners@haskell.org
Message-ID: 20120911054919.ga7...@gnu.kitenet.net
Content-Type: text/plain; charset=us-ascii

Brandon Allbery wrote:
 Probably an alias for backward compatibility; isAlpha is C-style ctype.h
 stuff, which was ASCII only, whereas isLetter is Unicode style.

Prelude Data.Char all (\c - isLetter c == isAlpha c) [minBound..maxBound]
True

Whew! You had me worried my code had unicode bugs.
isAlpha == isLetter

-- 
see shy jo
-- next part --
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 828 bytes
Desc: Digital signature
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120911/ec32fa57/attachment-0001.pgp

--

Message: 2
Date: Tue, 11 Sep 2012 09:52:05 +0400
From: Stayvoid stayv...@gmail.com
Subject: Re: [Haskell-beginners] Data.Char: isAlpha vs. isLetter
To: beginners beginners@haskell.org
Message-ID:
cak5fs_gqwj49hcmzn6g2skn5eo4rsh7fchmd8oyvadmjsbf...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

 Probably an alias for backward compatibility; isAlpha is C-style ctype.h
 stuff, which was ASCII only, whereas isLetter is Unicode style.

Both Haskell functions support non-ASCII chars.
Does it refute your assumption?

Thanks



--

___
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 51, Issue 15
*


Beginners Digest, Vol 51, Issue 16

2012-09-11 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  sometimes Haskell isn't what you want (Dennis Raddle)
   2. Re:  sometimes Haskell isn't what you want (Anindya Mozumdar)
   3. Re:  Data.Char: isAlpha vs. isLetter (Brandon Allbery)
   4. Re:  Data.Char: isAlpha vs. isLetter (Brandon Allbery)
   5.  Data.Map: fromList (Stayvoid)
   6. Re:  Data.Map: fromList (Brandon Allbery)


--

Message: 1
Date: Tue, 11 Sep 2012 05:16:15 -0700
From: Dennis Raddle dennis.rad...@gmail.com
Subject: Re: [Haskell-beginners] sometimes Haskell isn't what you want
To: Jay Sulzberger j...@panix.com
Cc: Haskell Beginners beginners@haskell.org
Message-ID:
CAKxLvor__0rv6rOfEB77oL4mgv11Pz-=ka8fzcutfaqc2e7...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

I went briefly to Python but guess what? I I U-turned right back to
Haskell. Because there is nothing like the consistent documentation and
well-thought-out libraries of Haskell. There is nothing else like the help
from #haskell or this list. I used to program in Python. I went back to it
for one day (yesterday) and that was enough to make me realize how
unpleasant its inconsistencies, inconsistent documentation, awkwardnesses,
etc. Maybe Haskell will make me think harder but at least the whole
language and supporting documentation and the whole community has got my
back. Haskell is a gift and I'm not throwing it away.

Yay!

On Mon, Sep 10, 2012 at 2:23 PM, Jay Sulzberger j...@panix.com wrote:



 On Sun, 9 Sep 2012, Dennis Raddle dennis.rad...@gmail.com wrote:

  Sadly, I've decided Haskell is not the right language for my current
 project. Python is better. I need to hack together data, and strict typing
 is getting in the way. Most of my algorithms are better served with
 imperative/mutable-data. I learned a lot about Haskell trying to do it,
 but
 my knowledge of the language is not quiet good enough and I feel like I'm
 fighting the language. Python is better. For now.


 I always recommend Scheme.

 It is like Haskell in one respect:

   The Scheme Tribes keep the Ritual and the Law of Lambda.

 Scheme is different from Haskell in two respects:

   We Lispers do all our coding under the Great Functor, the Great
   Functor from Code to Objects in the Lisp World.

   For most Scheme systems, the Type Sub-System calculates less at
   compile time.

 Robert Harper has a new textbook available at

   
 http://www.cs.cmu.edu/~rwh/**plbook/book.pdfhttp://www.cs.cmu.edu/~rwh/plbook/book.pdf

 and here is a useful notice of the book

   http://blog.ezyang.com/2012/**08/practical-foundations-for-**
 programming-languages/http://blog.ezyang.com/2012/08/practical-foundations-for-programming-languages/

 ad missing the Great Functor: See remarks on symbols in the
 section 32.3 on page 321, and the discussion of observational
 equivalence in section 47.1 on page 498.  A Lisper reading these
 sections might say Ah, the Great Functor is worthy of study by
 New Type Theorists too.  We Lispers consider a symbol to be a
 symbol first, and nothing else until you pass across one or more
 functors, and then the symbol might become many different
 things..

 ad dynamic typing vs static typing: Professor Harper's blog
 post

   http://existentialtype.**wordpress.com/2011/03/19/**
 dynamic-languages-are-static-**languages/http://existentialtype.wordpress.com/2011/03/19/dynamic-languages-are-static-languages/

 deals with this.  I think the claim made, that dynamic typing
 is a special case of static typing, is, when sympathetically
 read, right.

 oo--JS.


 __**_
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/**mailman/listinfo/beginnershttp://www.haskell.org/mailman/listinfo/beginners

-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120911/b360c162/attachment-0001.htm

--

Message: 2
Date: Tue, 11 Sep 2012 19:04:14 +0530
From: Anindya Mozumdar anindya.lugb...@gmail.com
Subject: Re: [Haskell-beginners] sometimes Haskell isn't what you want
To: Dennis Raddle dennis.rad...@gmail.com
Cc: Haskell Beginners beginners@haskell.org
Message-ID:
CADUR+2boDwjv25eFM_9Kbo_XQ4uUMn=syfjvvnuan7tgnb4...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

 I went back to it
 for one day (yesterday) and that was enough to make me realize how
 unpleasant its inconsistencies, 

Beginners Digest, Vol 51, Issue 17

2012-09-11 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  Reactive Banana Data Structures Sanity Check (Michael Litchard)
   2.  Playing and combining audio files (Tobias)
   3. Re:  sometimes Haskell isn't what you want (Darren Grant)
   4. Re:  sometimes Haskell isn't what you want (Mike Meyer)
   5. Re:  sometimes Haskell isn't what you want (Darren Grant)
   6. Re:  sometimes Haskell isn't what you want (Jay Sulzberger)
   7. Re:  sometimes Haskell isn't what you want (Michael Carpenter)
   8. Re:  Playing and combining audio files (Tom Murphy)


--

Message: 1
Date: Tue, 11 Sep 2012 11:38:17 -0700
From: Michael Litchard mich...@schmong.org
Subject: [Haskell-beginners] Reactive Banana Data Structures Sanity
Check
To: beginners@haskell.org
Message-ID:
caezekyp4gbaboysbu0eefbmqnv_3ywh3lxnsxd9hpfd2gve...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

I'm making an implementation of Grand Theft Wumpus using
reactive-banana. I'm using the slot machine example to work from.

For now, I'm just building a simple graph where a Player can move from
Node to Node. I'm not sure I have the Data Structures right, so I
wanted to run it by the community. I'm conceptualizing each Node (a
Street) and the Player as a Behavior.  I reason that since the Graph
won't change, just the values inside a Node, I can update any Node as
needed, instead of creating a new Graph whenever a value in a Node
changes. It seems though, as I scale up, I'd end up with a big union
of Behaviors.  Does it make sense to describe each Node as a Behavior?
Even though I'm starting simply, I intend to write a complete
implementiation.

http://nostarch.com/download/Lisp08.pdf

data StreetName = Baker
| Main
| Atlantic
| Baltic
| Connecticut
 deriving (Enum,Bounded,Show)


type Player t = Behavior t Player_
type Street t = Behavior t Street_


data Player_ = Player {location :: StreetName } deriving Show
data Street_ = Street_ {sName :: StreetName
   ,player :: Maybe Player_
   } deriving Show

data GameEvent = MovePlayer Street
   | Look

does that look okay so far?



--

Message: 2
Date: Tue, 11 Sep 2012 21:12:45 +0200
From: Tobias tobn...@freenet.de
Subject: [Haskell-beginners] Playing and combining audio files
To: beginners@haskell.org
Message-ID: 504f8d2d.5040...@freenet.de
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Hello,

I'm searching for a library with which I can process audio files (.wav 
or .mp3). All I need is functions with which I can
- play audio files
- concat several audio files to one audio file

Can you suggest a library for this task? I looked through 
http://hackage.haskell.org/packages/archive/pkg-list.html#cat:sound but 
I didn't manage to find ways to do this respectively sample code for this.

Any hints are welcome- thanks,
Tobias



--

Message: 3
Date: Tue, 11 Sep 2012 13:21:11 -0700
From: Darren Grant therealklu...@gmail.com
Subject: Re: [Haskell-beginners] sometimes Haskell isn't what you want
To: Anindya Mozumdar anindya.lugb...@gmail.com
Cc: Haskell Beginners beginners@haskell.org
Message-ID:
ca+jd6sghtef4ypzq0cunkqyuh8_h--z63cgz-0gndx5ebp1...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

Just adding another perspective: I developed the AI for a complex
turn-based strategy game in C++. By the end of the process I found
that I was not only continually repeating myself due to the language
syntax because I needed a *lot* of specialized list manipulations, but
I was also effectively composing pure functions.

This made me think that it could be much more effective to develop AI
in a functional language. There's no way I could do this with Haskell
presently as I am still struggling to approach all problems from the
FP perspective first, but I do think there is the potential.


Cheers,
Darren



On Tue, Sep 11, 2012 at 6:34 AM, Anindya Mozumdar
anindya.lugb...@gmail.com wrote:
 I went back to it
 for one day (yesterday) and that was enough to make me realize how
 unpleasant its inconsistencies, inconsistent documentation, awkwardnesses,
 etc.

 Haskell is a gift and I'm not throwing it away.

 Luckily this is a small list, otherwise a flame war would have started by now.

 Personally, I learnt the basics of Haskell in the year 2000 in
 college. I am 

Beginners Digest, Vol 51, Issue 19

2012-09-12 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  Question about time consume when calculate prime numbers
  (Yi Cheng)
   2. Re:  Question about time consume when calculate prime numbers
  (Lorenzo Bolla)
   3. Re:  Question about time consume when calculate prime numbers
  (Yi Cheng)


--

Message: 1
Date: Wed, 12 Sep 2012 20:17:54 +0800
From: Yi Cheng chengyi...@gmail.com
Subject: Re: [Haskell-beginners] Question about time consume when
calculate prime numbers
To: Lorenzo Bolla lbo...@gmail.com
Cc: beginners@haskell.org
Message-ID:
caek-nmenqhk4ww6kdi-6dwwarrfzz3nqxx0rgknu0l7sehe...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

Thanks for answering my question, but I'm still confused by some details.
I don't quite agree with you that Eratosthenes algorithm must be
implemented with a complexity of O(n^2) in space. When the n is used to
calculate the primes below it, it can be implemented in space complexity
O(n). For example, in languages, like C/C++, we can allocate a array. So I
think the the complexity of O(n^2) in space you mentioned, is the
complexity of the beautiful code. So here's the question, can
Eratosthenes algorithm be implemented in a more gentle way?

Then I think maybe there is a more beautiful and practical way to implement
it.
One method of mine is trying to judge whether a number is a prime just by
the primes less than it, such as if the greatest common divisor of the
number and the product of the primes less than it equals to 1. But the
product of the primes is too large.

So I wander if there is a concise method to solve the problem with a faster
method. In my C++ version, the Eratosthenes is implemented in linear space
complexity, and optimize in filtering the numbers which can be divided by a
prime. This code is faster than the original algorithm implemented by me(It
was also implemented it in C++, and slower than the following code).
I know, when writing Haskell code, it would be better to forget some
experience in command-line language, but I want to know whether there is a
faster method to solve the problem.


Thank you.
Yi. Cheng

The code in my c++ version.
#include iostream
using namespace std;
int main(){
int p[200] = {0};
long sum = 0;
int f = 1;
for(long i=2; i = 200; ++i){
if(p[i] == 0){
sum += i;
for(long j = i * i; j  200; j += i)
p[j] = 1;
}
}
coutsumendl;
return 0;
}

On Wed, Sep 12, 2012 at 5:26 PM, Lorenzo Bolla lbo...@gmail.com wrote:



 On Wed, Sep 12, 2012 at 9:06 AM, Yi Cheng chengyi...@gmail.com wrote:

 Recently, I'm trying to solve some problems in project euler using
 haskell. When it came to problem 10, calculating the sum of all primes
 below 2000, I try to write a program which can generate primes.
 In my memory Eratosthenes is faster than just whether a number can be
 divided by the number less then the square root of it.
 Firstly, I wrote the following programs:

 module Main where
 isPrime x = isPrime' 3 x (round . sqrt. fromIntegral $ x)
 isPrime' d target maxd
   | d  maxd = True
   | mod target d == 0 = False
   | otherwise = isPrime' (d + 2) target maxd

 main = print $ (sum (filter isPrime [3,5..200]) + 2)

 And it consume about 11s in my computer.
 Then, I tried to figure out how to solve the problem by Eratosthenes, but
 failed. Later, I find a program implemented by others, meeting my purpose
 and I've used it to solve the problem:

 primes :: [Int]
 primes = primes' [2..]

 primes' :: [Int] - [Int]
 primes' [] = []
 primes' (n:ns) = n : primes' (filter (\v - v `mod` n /= 0) ns)

 solve x = sum $ primes' [2..x]

 main = print $ solve 200

 Well, although the code is beautiful, it is slow. Even waiting for a
 minute, no answer was printed.

 In C version, Eratosthenes is faster than the method implemented in my
 earlier code, which only consume 0.3s(the earlier method consume 1.6s).

 So I want to know, why Eratosthenes implemented in Haskell is slow than
 the ugly code implemented by me.
 Could anyone tell me?


 Eratosthenes's complexity is O(n^2) (both space and time), whereas the
 ugly one has a sub-quadratic running complexity and linear in space.

 Try to profile them:
 $ ghc -O2 --make -prof -auto-all filename
 $ ./primes +RTS -p -hc
 $ hp2ps primes.hp

 You'll see that most of the time is spent allocating space which is never
 released.
 You could play a bit with 

Beginners Digest, Vol 51, Issue 20

2012-09-13 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1.  Haskell for Android (Miroslav Karpis)
   2. Re:  Haskell for Android (Henk-Jan van Tuyl)
   3. Re:  Question about time consume when calculate prime numbers
  (Fletcher Stump Smith)
   4.  cyclic imports (Christopher Howard)
   5. Re:  cyclic imports (Chadda? Fouch?)


--

Message: 1
Date: Wed, 12 Sep 2012 19:21:28 +0200
From: Miroslav Karpis miroslav.kar...@gmail.com
Subject: [Haskell-beginners] Haskell for Android
To: Beginners@haskell.org
Message-ID: 462f4004-91b0-42aa-a947-251be3fc9...@gmail.com
Content-Type: text/plain; charset=windows-1252

Hi haskellers, please can you help me with this? I read several posts about it, 
but unfortunately it is still not clear. What is (if there is) the most 
straight way to port haskell code to android?

Translate haskell to c or javascript? Not sure how debugging will work this 
way?. ?

thanks,
m.


--

Message: 2
Date: Wed, 12 Sep 2012 22:30:57 +0200
From: Henk-Jan van Tuyl hjgt...@chello.nl
Subject: Re: [Haskell-beginners] Haskell for Android
To: Beginners@haskell.org, Miroslav Karpis
miroslav.kar...@gmail.com
Message-ID: op.wkjhxvl5pz0...@zen5.arnhem.chello.nl
Content-Type: text/plain; charset=utf-8; format=flowed; delsp=yes

On Wed, 12 Sep 2012 19:21:28 +0200, Miroslav Karpis  
miroslav.kar...@gmail.com wrote:

 Hi haskellers, please can you help me with this? I read several posts  
 about it, but unfortunately it is still not clear. What is (if there is)  
 the most straight way to port haskell code to android?

There is a HaskellWiki page for Android[0] with some interesting links.

This article is a stub; anyone who is an expert in this area, please add  
more info.

Regards,
Henk-Jan van Tuyl

[0] http://www.haskell.org/haskellwiki/Android

-- 
http://Van.Tuyl.eu/
http://members.chello.nl/hjgtuyl/tourdemonad.html
Haskell programming
--



--

Message: 3
Date: Wed, 12 Sep 2012 15:32:13 -0700
From: Fletcher Stump Smith fletcher...@gmail.com
Subject: Re: [Haskell-beginners] Question about time consume when
calculate prime numbers
To: Yi Cheng chengyi...@gmail.com
Cc: beginners@haskell.org
Message-ID:
CAPEBXRzXt+LNGHDSgWBgpniS34wZxt+HZobA=anox9krwht...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

You might also be interested in this paper:
www.cs.hmc.edu/~oneill/papers/Sieve-JFP.pdf . I thought it was a good
analysis/

On Wed, Sep 12, 2012 at 8:53 AM, Yi Cheng chengyi...@gmail.com wrote:
 Thank you, very much. It's exactly the thing I want to know.

 Yi. Cheng


 On Wed, Sep 12, 2012 at 8:41 PM, Lorenzo Bolla lbo...@gmail.com wrote:



 On Wed, Sep 12, 2012 at 1:17 PM, Yi Cheng chengyi...@gmail.com wrote:


 Thanks for answering my question, but I'm still confused by some details.
 I don't quite agree with you that Eratosthenes algorithm must be
 implemented with a complexity of O(n^2) in space. When the n is used to
 calculate the primes below it, it can be implemented in space complexity
 O(n). For example, in languages, like C/C++, we can allocate a array. So I
 think the the complexity of O(n^2) in space you mentioned, is the complexity
 of the beautiful code. So here's the question, can Eratosthenes algorithm
 be implemented in a more gentle way?


 Correct: I referred to your implementation. See here
 (http://www.haskell.org/haskellwiki/Prime_numbers#Sieve_of_Eratosthenes) for
 many different (and more efficient) implementations of Eratosthenes.


 Then I think maybe there is a more beautiful and practical way to
 implement it.
 One method of mine is trying to judge whether a number is a prime just by
 the primes less than it, such as if the greatest common divisor of the
 number and the product of the primes less than it equals to 1. But the
 product of the primes is too large.

 So I wander if there is a concise method to solve the problem with a
 faster method. In my C++ version, the Eratosthenes is implemented in linear
 space complexity, and optimize in filtering the numbers which can be divided
 by a prime. This code is faster than the original algorithm implemented by
 me(It was also implemented it in C++, and slower than the following code).
 I know, when writing Haskell code, it would be better to forget some
 experience in command-line language, but I want to know whether there is a
 faster method to solve the problem.


 Thank you.
 Yi. Cheng

 The code in my c++ version.
 

Beginners Digest, Vol 51, Issue 22

2012-09-15 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  Reactive Banana Data Structures Sanity Check
  (Heinrich Apfelmus)
   2.  Comfortable handling of module hierarchies (Christopher Howard)
   3.  Algorithmic Advances by Discovering Patterns in  Functions
  (Costello, Roger L.)


--

Message: 1
Date: Fri, 14 Sep 2012 15:45:49 +0200
From: Heinrich Apfelmus apfel...@quantentunnel.de
Subject: Re: [Haskell-beginners] Reactive Banana Data Structures
Sanity Check
To: beginners@haskell.org
Message-ID: k2vcec$du1$1...@ger.gmane.org
Content-Type: text/plain; charset=UTF-8; format=flowed

Michael Litchard wrote:
 I'm making an implementation of Grand Theft Wumpus using
 reactive-banana. I'm using the slot machine example to work from.
 
 For now, I'm just building a simple graph where a Player can move from
 Node to Node. I'm not sure I have the Data Structures right, so I
 wanted to run it by the community. I'm conceptualizing each Node (a
 Street) and the Player as a Behavior.  I reason that since the Graph
 won't change, just the values inside a Node, I can update any Node as
 needed, instead of creating a new Graph whenever a value in a Node
 changes. It seems though, as I scale up, I'd end up with a big union
 of Behaviors.  Does it make sense to describe each Node as a Behavior?
 Even though I'm starting simply, I intend to write a complete
 implementiation.
 
 http://nostarch.com/download/Lisp08.pdf
 
 data StreetName = [...]
 
 type Player t = Behavior t Player_
 type Street t = Behavior t Street_
 
 data Player_ = Player {location :: StreetName } deriving Show
 data Street_ = Street_ {sName :: StreetName
,player :: Maybe Player_
} deriving Show
 
 data GameEvent = MovePlayer Street
| Look
 
 does that look okay so far?

That's hard to say. It certainly doesn't look wrong, but whether it's a 
good idea or not depends on what you will do later.


My process for programming with Functional Reactive Programming (FRP) is 
  usually this:

* What is the end product, i.e. the thing that users ultimately 
interact with? In your case, it's probably the drawing of a map of the city.

* Does the end product vary in time? Yes? Then it's going to be a 
Behavior City  , i.e. a data structure that describes the evolution of 
the city in time.

* How does the city evolve in time? Here I start to think of the events 
and other behaviors that I use to define the behavior, for instance by 
writing

 bcity :: Behavior City
 bcity = stepper ... -- step function from events

or

 bcity = (++) $ bsuburbs * bcenter  -- combine other behaviors

and so on.


The process is a bit like thinking as a physicist in god-mode: for each 
object in my little universe, I specify where it should be at any 
particular time, like 5 o'clock.


That said, I found it useful to decouple the interaction of individual 
parts -- city, node, player -- from their time evolution. Have a look at 
the Asteroids.hs example

http://www.haskell.org/haskellwiki/Reactive-banana/Examples#asteroids

The bottom part of the source contains function like  advanceRocks  or 
collide  that specify more complicated interactions between different 
objects. The FRP part of the source file just specifies *when* these 
interactions take place, i.e.  advanceRocks  happens when  etick 
happens  while the player moves when  eleft  or  eright  happen.

In other words, my rule of thumb is

   How  does it happen? = ordinary functions
   When does it happen? = events and behaviors

In particular, you can write your Wumpus game logic by asking the how 
questions first and only then ask the when questions. Thus, I would 
rename  Player_  to  Player  for the how part and simply use  Behavior 
t Player  for the fairly small when part.

Hope that helps.


Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com




--

Message: 2
Date: Fri, 14 Sep 2012 17:23:45 -0800
From: Christopher Howard christopher.how...@frigidcode.com
Subject: [Haskell-beginners] Comfortable handling of module
hierarchies
To: Haskell Beginners beginners@haskell.org
Message-ID: 5053d8a1.7030...@frigidcode.com
Content-Type: text/plain; charset=iso-8859-1

So, let's say I've got this hierarchy of modules:

Plant
  `-- Vegetable
  |`-- Celery
  |`-- Lettuce
  `-- Fruit
   `-- Raspberry
   `-- Apple

What I would like to be able to do is import and 

Beginners Digest, Vol 51, Issue 23

2012-09-16 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  Comfortable handling of module hierarchies (Karl Voelker)
   2.  FRP (Christopher Howard)
   3. Re:  FRP (Ertugrul S?ylemez)
   4. Re:  FRP (Ertugrul S?ylemez)
   5. Re:  FRP (Christopher Howard)
   6. Re:  FRP (Ertugrul S?ylemez)


--

Message: 1
Date: Sat, 15 Sep 2012 09:00:55 -0700
From: Karl Voelker ktvoel...@gmail.com
Subject: Re: [Haskell-beginners] Comfortable handling of module
hierarchies
To: Christopher Howard christopher.how...@frigidcode.com
Cc: Haskell Beginners beginners@haskell.org
Message-ID:
CAFfow0zM4QsP_3m_8Qx8JrCxa3-FXDzi89H4XoWXzP8uLs=m...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

On Fri, Sep 14, 2012 at 6:23 PM, Christopher Howard
christopher.how...@frigidcode.com wrote:

 import qualified Plant as P

 P.Fruit.Raspberry.jam

Short answer: P.Fruit.Raspberry.jam would work if you said:

import qualified Plant.Fruit.Raspberry as P.Fruit.Raspberry

Long answer:

You can't have exactly what you want because the Haskell module
namespace isn't exactly heirarchical. Here's an excerpt from the
Haskell 98 report [1]:

The name-space for modules themselves is flat, with each module being
associated with a unique module name (which are Haskell identifiers
beginning with a capital letter; i.e. modid).

Notice that this doesn't allow for dots in module names. A
commonly-provided language extension allowed dots in module names, and
compilers took these dots as a signal to look for a module's source at
a particular place in the directory tree, but the semantics of the
language didn't have a heirarchy of modules.

Things haven't changed much in Haskell 2010, other than the existing
use of dots being formalized [2]:

Module names can be thought of as being arranged in a hierarchy in
which appending a new component creates a child of the original module
name. For example, the module Control.Monad.ST is a child of the
Control.Monad sub-hierarchy. This is purely a convention, however, and
not part of the language definition; in this report a modid is treated
as a single identifier occupying a flat namespace.

In your code snippet, P.Fruit.Raspberry doesn't work because although
P refers to the same module as Plant, there isn't anything inside P
(or Plant) called Fruit.Raspberry.

-Karl

[1] http://www.haskell.org/onlinereport/modules.html
[2] http://www.haskell.org/onlinereport/haskell2010/haskellch5.html#x11-980005



--

Message: 2
Date: Sat, 15 Sep 2012 22:15:04 -0800
From: Christopher Howard christopher.how...@frigidcode.com
Subject: [Haskell-beginners] FRP
To: Haskell Beginners beginners@haskell.org
Message-ID: 50556e68.1000...@frigidcode.com
Content-Type: text/plain; charset=iso-8859-1

Hi. I'm trying to understand what Functional Reactive Programming is,
or, more properly, what distinguishes it from regular functional
programming, and what it would look like if I were to program in a FRP
Style, i.e., without some mysterious FRP module hiding the details.
After reading a bunch of links and even looking at some source code I'm
still not clear on this.

If I program in an event-based style, and have data structures updating
over time, with some data structures dependent on others for their
values, and I use a functional language, is that FRP? Or is there some
essential element I'm missing here?

-- 
frigidcode.com
indicium.us

-- next part --
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 551 bytes
Desc: OpenPGP digital signature
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120915/944bf65e/attachment-0001.pgp

--

Message: 3
Date: Sun, 16 Sep 2012 09:16:19 +0200
From: Ertugrul S?ylemez e...@ertes.de
Subject: Re: [Haskell-beginners] FRP
To: beginners@haskell.org
Message-ID: 20120916091619.44ace...@tritium.streitmacht.eu
Content-Type: text/plain; charset=us-ascii

Christopher Howard christopher.how...@frigidcode.com wrote:

 Hi. I'm trying to understand what Functional Reactive Programming is,
 or, more properly, what distinguishes it from regular functional
 programming, and what it would look like if I were to program in a
 FRP Style, i.e., without some mysterious FRP module hiding the
 details. After reading a bunch of links and even looking at some
 source code I'm still not clear on this.

 If I program in an event-based style, and have data 

Beginners Digest, Vol 51, Issue 24

2012-09-16 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  Comfortable handling of module hierarchies (damodar kulkarni)
   2. Re:  FRP (Henk-Jan van Tuyl)
   3. Re:  FRP (Ertugrul S?ylemez)
   4. Re:  Comfortable handling of module hierarchies (Edward Z. Yang)
   5. Re:  Comfortable handling of module hierarchies (damodar kulkarni)
   6. Re:  Comfortable handling of module hierarchies (Brandon Allbery)
   7. Re:  FRP (Heinrich Apfelmus)


--

Message: 1
Date: Sun, 16 Sep 2012 16:07:41 +0530
From: damodar kulkarni kdamodar2...@gmail.com
Subject: Re: [Haskell-beginners] Comfortable handling of module
hierarchies
To: Karl Voelker ktvoel...@gmail.com
Cc: Haskell Beginners beginners@haskell.org
Message-ID:
CAD5HsyoeY0_RSGYC7SzTB=R=onngrerw+wc3vdnpmeskwvo...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

Do you know any document pointing out the rationale behind this decision
about modules taken by the Haskell designers?

Thanks.
-Damodar

On Sat, Sep 15, 2012 at 9:30 PM, Karl Voelker ktvoel...@gmail.com wrote:

 On Fri, Sep 14, 2012 at 6:23 PM, Christopher Howard
 christopher.how...@frigidcode.com wrote:
 
  import qualified Plant as P
 
  P.Fruit.Raspberry.jam

 Short answer: P.Fruit.Raspberry.jam would work if you said:

 import qualified Plant.Fruit.Raspberry as P.Fruit.Raspberry

 Long answer:

 You can't have exactly what you want because the Haskell module
 namespace isn't exactly heirarchical. Here's an excerpt from the
 Haskell 98 report [1]:

 The name-space for modules themselves is flat, with each module being
 associated with a unique module name (which are Haskell identifiers
 beginning with a capital letter; i.e. modid).

 Notice that this doesn't allow for dots in module names. A
 commonly-provided language extension allowed dots in module names, and
 compilers took these dots as a signal to look for a module's source at
 a particular place in the directory tree, but the semantics of the
 language didn't have a heirarchy of modules.

 Things haven't changed much in Haskell 2010, other than the existing
 use of dots being formalized [2]:

 Module names can be thought of as being arranged in a hierarchy in
 which appending a new component creates a child of the original module
 name. For example, the module Control.Monad.ST is a child of the
 Control.Monad sub-hierarchy. This is purely a convention, however, and
 not part of the language definition; in this report a modid is treated
 as a single identifier occupying a flat namespace.

 In your code snippet, P.Fruit.Raspberry doesn't work because although
 P refers to the same module as Plant, there isn't anything inside P
 (or Plant) called Fruit.Raspberry.

 -Karl

 [1] http://www.haskell.org/onlinereport/modules.html
 [2]
 http://www.haskell.org/onlinereport/haskell2010/haskellch5.html#x11-980005

 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners

-- next part --
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120916/bb143a37/attachment-0001.htm

--

Message: 2
Date: Sun, 16 Sep 2012 13:05:23 +0200
From: Henk-Jan van Tuyl hjgt...@chello.nl
Subject: Re: [Haskell-beginners] FRP
To: beginners@haskell.org, Ertugrul S?ylemez e...@ertes.de
Message-ID: op.wkp6e9mvpz0...@zen5.arnhem.chello.nl
Content-Type: text/plain; charset=iso-8859-15; format=flowed;
delsp=yes


Hello Ertugrul,

Can I use your explanation for the HaskellWiki FRP page[0]?

Regards,
Henk-Jan van Tuyl


[0] http://www.haskell.org/haskellwiki/Functional_Reactive_Programming


-- 
http://Van.Tuyl.eu/
http://members.chello.nl/hjgtuyl/tourdemonad.html
Haskell programming
--



--

Message: 3
Date: Sun, 16 Sep 2012 13:21:57 +0200
From: Ertugrul S?ylemez e...@ertes.de
Subject: Re: [Haskell-beginners] FRP
To: beginners@haskell.org
Message-ID: 20120916132157.79af1...@tritium.streitmacht.eu
Content-Type: text/plain; charset=us-ascii

Henk-Jan van Tuyl hjgt...@chello.nl wrote:

 Can I use your explanation for the HaskellWiki FRP page[0]?

Sure.


Greets,
Ertugrul

-- 
Not to be or to be and (not to be or to be and (not to be or to be and
(not to be or to be and ... that is the list monad.
-- next part --
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 

Beginners Digest, Vol 51, Issue 25

2012-09-17 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  Algorithmic Advances by Discovering Patterns in
  Functions (Darren Grant)
   2.  trouble with install SDL? (Gregory Guthrie)


--

Message: 1
Date: Sun, 16 Sep 2012 11:11:34 -0700
From: Darren Grant therealklu...@gmail.com
Subject: Re: [Haskell-beginners] Algorithmic Advances by Discovering
Patterns in Functions
To: beginners@haskell.org beginners@haskell.org
Message-ID:
ca+jd6sit+kiisecnb3kuzdqfct8ydumgepfhs_7ky6b9+_k...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

Thanks for this!


On Sat, Sep 15, 2012 at 1:36 AM, Costello, Roger L. coste...@mitre.org wrote:
 Hi Folks,

 This is a story about discovery. It is a story about advancing the 
 state-of-the-art by discovering patterns in functions.

 Scientists look for recurring patterns in nature. Once a pattern is 
 discovered, its essential ingredients are identified and formalized into a 
 law or mathematical equation. Discovery of a pattern is important and those 
 individuals who make such discoveries are rightfully acknowledged in our 
 annals of science.

 Scientists are not the only ones who look for recurring patterns, so do 
 functional programmers. Once a pattern is discovered, its essential 
 ingredients are identified and formalized into a function. That function may 
 then become widely adopted by the programming community, thus elevating the 
 programming community to a new level of capability.

 The following is a fantastic example of discovering a pattern in multiple 
 functions, discerning the essential ingredients of the pattern, and replacing 
 the multiple functions with a single superior function. The example is from 
 Richard Bird's book, Introduction to Functional Programming using Haskell.

 Before looking at the example let's introduce an important concept in 
 functional programming: partial function application.

 A function that takes two arguments may be rewritten as a function that takes 
 one argument and returns a function. The function returned also takes one 
 argument. For example, consider the min function which returns the minimum of 
 two integers:

 min 2 3 -- returns 2

 Notice that min is a function that takes two arguments.

 Suppose min is given only one argument:

 min 2

 [Definition: When fewer arguments are given to a function than it can accept 
 it is called partial application of the function.  That is, the function is 
 partially applied.]

 min 2 is a function. It takes one argument. It returns the minimum of the 
 argument and 2. For example:

 (min 2) 3   -- returns 2

 To see this more starkly, let's assign g to be the function min 2:

 let g = min 2

 g is now a function that takes one argument and returns the minimum of the 
 argument and 2:

 g 3 -- returns 2

 Let's take a second example: the addition operator (+) is a function and it 
 takes two arguments. For example:

 2 + 3   -- returns 5

 To make it more obvious that (+) is a function, here is the same example in 
 prefix notation:

 (+) 2 3 -- returns 5

 Suppose we provide (+) only one argument:

 (+) 2

 That is a partial application of the (+) function.

 (+) 2 is a function. It takes one argument. It returns the sum of the 
 argument and 2. For example:

 ((+) 2) 3   -- returns 5

 We can succinctly express (+) 2 as:

 (+2)

 Thus,

 (+2) 3  -- returns 5

 Okay, now we are ready to embark on our journey of discovery. We will examine 
 three functions and find their common pattern.

 The functions process values from this recursive data type:

 data Nat = Zero | Succ Nat

 Here are some examples of Nat values:

 Zero, Succ Zero, Succ (Succ Zero), Succ (Succ (Succ Zero)), ...

 The following functions perform addition, multiplication, and exponentiation 
 on Nat values. Examine the three functions. Can you discern a pattern?

 -- Addition of Nat values:
 m + Zero = m
 m + Succ n = Succ(m + n)

 -- Multiplication of Nat values:
 m * Zero = Zero
 m * Succ n = (m * n) + m

 -- Exponentiation of Nat values:
 m ** Zero = Succ Zero
 m ** Succ n = (m ** n) * m

 For each function the right-hand operand is either Zero or Succ n:

 (+m) Zero
 (+m) Succ n

 (*m) Zero
 (*m) Succ n

 (**m) Zero
 (**m) Succ n

 So abstractly there is a function f that takes as argument either Zero or 
 Succ n:

 f Zero
 f Succ n

 Given Zero as the argument, each function immediately returns a value:

 (+m)  Zero  = m
 (*m)  Zero   

Beginners Digest, Vol 51, Issue 26

2012-09-18 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  trouble with install SDL? (Stephen Tetley)
   2.  Sending mail via SMTP (Salil Wadnerkar)
   3. Re:  Algorithmic Advances by Discovering Patterns in
  Functions (Kim-Ee Yeoh)


--

Message: 1
Date: Mon, 17 Sep 2012 17:49:52 +0100
From: Stephen Tetley stephen.tet...@gmail.com
Subject: Re: [Haskell-beginners] trouble with install SDL?
To: Gregory Guthrie guth...@mum.edu
Cc: beginners@haskell.org beginners@haskell.org
Message-ID:
cab2tprastwzz1gwm1j2qy2+4ayjxshchai9x2nfrrvzetkn...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

Hi Gergory

You want to build the binding under MinGW / SYS using the development
headers and libraries from libsdl.org packaged as
SDL-devel-1.2.15-mingw32.tar.gz (or a later version if there is one).

SDL-devel-1.12.15-mingw32.tar.gz installs easily after unpacking (I
believe it ships mostly binary components rather than builds anything
much from source).


To build the Haskell binding you want to tell Cabal to use these libs:

   Extra-Libraries: SDL.dll SDLmain

Additionally point to the extra devel and lib dirs - for me with a
vanilla install of SDL-devel-1.12.15-mingw32.tar.gz they located in
these directories:

  Include-Dirs:   C:\msys\1.0\include\SDL

SDL includes the toplevel header SDL.h, plus others.

  Extra-Lib-Dirs: C:\msys\1.0\lib

which should contain libSDL.dll.a, libSDL.la, and libSDLmain.a

I modified my local SDL.cabal file to include these changes (otherwise
I'd likely forget them if I needed to rebuild), but you should be able
to pass them as options to  runhaskell Set.lhs configure

Regards

Stephen



--

Message: 2
Date: Tue, 18 Sep 2012 07:32:45 +0800
From: Salil Wadnerkar rohsh...@gmail.com
Subject: [Haskell-beginners] Sending mail via SMTP
To: beginners@haskell.org
Message-ID:
cahrrg0ovv8-+zsicn75fhuu6t3r6c8a4xwykaau24er7wb4...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

Hi,

Does anybody know of any good libraries I can use to send a mail via
google's SMTP? I found SMTPClient and HaskellNet. The former does not
support TLS and the latter does not seem to have examples for using
TLS to send an email via SMTP. Did anybody manage to do that?

Thanks
Salil



--

Message: 3
Date: Tue, 18 Sep 2012 15:56:12 +0700
From: Kim-Ee Yeoh k...@atamo.com
Subject: Re: [Haskell-beginners] Algorithmic Advances by Discovering
Patterns in Functions
To: Costello, Roger L. coste...@mitre.org
Cc: beginners@haskell.org beginners@haskell.org
Message-ID:
capy+zdqwrtbm8eyq7dr1drlbhg3uf5wfad5lrnj7kv18uaz...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

Roger,

  Scientists look for recurring patterns in nature. Once a pattern is
discovered, its essential ingredients are identified and formalized into a
law or mathematical equation.

You could think of lambda calculus as a general language for formalizing
and applying patterns. Squint enough and pinning down a pattern starts to
look like lambda abstraction; using the pattern, function application.

 Here is some intuition on why it is called the fold function: Imagine
folding a towel.

Generally we don't look for insight in the layperson meaning of technical
terminology. Sure, folding a list is intuitively like folding a long strip
of paper. But folds also apply to trees and even gnarlier datatypes, and
there intuition loses steam.

Sometimes it's better to internally alpha-rename to a fresh variable to
avoid being misled. The meaning lies in the *usage* of the term, so in a
way it's not really in English after all.

 We saw that the fold function can be defined for the Nat data type. In
fact, a suitable fold function can be defined for every recursive data type.

How would you define a fold for

data S a = S (a - Bool)

?


-- Kim-Ee


On Sat, Sep 15, 2012 at 3:36 PM, Costello, Roger L. coste...@mitre.org
 wrote:

 Hi Folks,

 This is a story about discovery. It is a story about advancing the
 state-of-the-art by discovering patterns in functions.

 Scientists look for recurring patterns in nature. Once a pattern is
 discovered, its essential ingredients are identified and formalized into a
 law or mathematical equation. Discovery of a pattern is important and those
 individuals who make such discoveries are rightfully acknowledged in our
 annals of science.

 Scientists are not the only ones who look for recurring patterns, so 

Beginners Digest, Vol 51, Issue 27

2012-09-18 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  Sending mail via SMTP (Anindya Mozumdar)
   2. Re:  Sending mail via SMTP (Salil Wadnerkar)
   3. Re:  Sending mail via SMTP (Robert Wills)
   4. Re:  Sending mail via SMTP (Tim Perry)
   5. Re:  FRP (Christopher Howard)
   6. Re:  Algorithmic Advances by Discovering Patterns in
  Functions (Jay Sulzberger)
   7. Re:  FRP (Darren Grant)


--

Message: 1
Date: Tue, 18 Sep 2012 20:10:30 +0530
From: Anindya Mozumdar anindya.lugb...@gmail.com
Subject: Re: [Haskell-beginners] Sending mail via SMTP
To: Salil Wadnerkar rohsh...@gmail.com
Cc: beginners@haskell.org
Message-ID:
cadur+2yhk4fbplguo5x01qtwy2aaxaf4fncyyx4wcnwvjqu...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

 Does anybody know of any good libraries I can use to send a mail via
 google's SMTP? I found SMTPClient and HaskellNet. The former does not
 support TLS and the latter does not seem to have examples for using
 TLS to send an email via SMTP. Did anybody manage to do that?


A fellow beginner, so I don't have indepth knowledge of the subject.

But can this help -

http://stackoverflow.com/questions/8036680/haskell-smtp-over-ssl

http://www.haskell.org/pipermail/beginners/2012-July/010190.html



--

Message: 2
Date: Tue, 18 Sep 2012 23:08:50 +0800
From: Salil Wadnerkar rohsh...@gmail.com
Subject: Re: [Haskell-beginners] Sending mail via SMTP
To: Anindya Mozumdar anindya.lugb...@gmail.com
Cc: beginners@haskell.org
Message-ID:
CAHRrG0rMHFLoo7L__VPr_CJL0QYhd3oy+VMvWDAffjLazC=g...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

Hi Aninda,

Thanks for your reply. Unfortunately, I have already tried out these
examples and they don't seem to work.
HaskellNet has a github repo. I will contact the author and see
whether I can find any solution.

Thanks
Salil

On Tue, Sep 18, 2012 at 10:40 PM, Anindya Mozumdar
anindya.lugb...@gmail.com wrote:
 Does anybody know of any good libraries I can use to send a mail via
 google's SMTP? I found SMTPClient and HaskellNet. The former does not
 support TLS and the latter does not seem to have examples for using
 TLS to send an email via SMTP. Did anybody manage to do that?


 A fellow beginner, so I don't have indepth knowledge of the subject.

 But can this help -

 http://stackoverflow.com/questions/8036680/haskell-smtp-over-ssl

 http://www.haskell.org/pipermail/beginners/2012-July/010190.html



--

Message: 3
Date: Tue, 18 Sep 2012 17:41:52 +0100
From: Robert Wills wrwi...@gmail.com
Subject: Re: [Haskell-beginners] Sending mail via SMTP
To: Salil Wadnerkar rohsh...@gmail.com
Cc: beginners@haskell.org
Message-ID:
CALVz20_wHYys0eR4eC-px9-zaXyF+0k9_rt36U7Fihk=ud5...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

I do not believe there is and support for ssl in HaskellNet at
present.  It has I believe
been looked at but it's not simple to implement.  The best way of
integrating tls would
be to implement smtp over conduit as http-conduit does.

On Tue, Sep 18, 2012 at 4:08 PM, Salil Wadnerkar rohsh...@gmail.com wrote:
 Hi Aninda,

 Thanks for your reply. Unfortunately, I have already tried out these
 examples and they don't seem to work.
 HaskellNet has a github repo. I will contact the author and see
 whether I can find any solution.

 Thanks
 Salil

 On Tue, Sep 18, 2012 at 10:40 PM, Anindya Mozumdar
 anindya.lugb...@gmail.com wrote:
 Does anybody know of any good libraries I can use to send a mail via
 google's SMTP? I found SMTPClient and HaskellNet. The former does not
 support TLS and the latter does not seem to have examples for using
 TLS to send an email via SMTP. Did anybody manage to do that?


 A fellow beginner, so I don't have indepth knowledge of the subject.

 But can this help -

 http://stackoverflow.com/questions/8036680/haskell-smtp-over-ssl

 http://www.haskell.org/pipermail/beginners/2012-July/010190.html

 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners



--

Message: 4
Date: Tue, 18 Sep 2012 10:01:14 -0700
From: Tim Perry tim.v...@gmail.com
Subject: Re: [Haskell-beginners] Sending mail via SMTP
To: beginners@haskell.org
Message-ID:
cafvgasxhhm6op0gqfiawmt0j4k9ynvztchnxvipjgqy0ksy...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

Robert,

are you saying you 

Beginners Digest, Vol 51, Issue 28

2012-09-19 Thread beginners-request
Send Beginners mailing list submissions to
beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
beginners-requ...@haskell.org

You can reach the person managing the list at
beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than Re: Contents of Beginners digest...


Today's Topics:

   1. Re:  FRP (Ertugrul S?ylemez)
   2. Re:  FRP (Darren Grant)
   3. Re:  FRP (Kim-Ee Yeoh)


--

Message: 1
Date: Wed, 19 Sep 2012 04:35:18 +0200
From: Ertugrul S?ylemez e...@ertes.de
Subject: Re: [Haskell-beginners] FRP
To: beginners@haskell.org
Message-ID: 20120919043518.543d2...@tritium.streitmacht.eu
Content-Type: text/plain; charset=us-ascii

Christopher Howard christopher.how...@frigidcode.com wrote:

 Which FRP framework (i.e., Haskell package) is the best one to play
 with for someone still trying to grasp the basics of FRP?

In terms of tutorials and related blog posts I currently recommend
reactive-banana.  In terms of power and elegance I recommend Netwire.

The main difference is that reactive-banana is both simple and easy.  It
implements classic FRP with the usual notion of behaviors and events.
Heinrich strives to make it very accessible.

Netwire follows a more algebraic path and drops the classic notion.  The
line between signals and events is blurred.  It's a bit more difficult
to understand, but is more expressive and concise.  Also it's pretty
much time-leak-free.  The library is designed to be very elegant while
preserving non-FRP performance to a high degree.

(To be fair, I'm the author of Netwire.) =)


Greets,
Ertugrul

-- 
Not to be or to be and (not to be or to be and (not to be or to be and
(not to be or to be and ... that is the list monad.
-- next part --
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 836 bytes
Desc: not available
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20120919/df664793/attachment-0001.pgp

--

Message: 2
Date: Tue, 18 Sep 2012 23:12:47 -0700
From: Darren Grant therealklu...@gmail.com
Subject: Re: [Haskell-beginners] FRP
To: Ertugrul S?ylemez e...@ertes.de
Cc: beginners@haskell.org
Message-ID:
ca+jd6siwczslat-wcj6emvp4-2klncne5jib7heft+v7+6m...@mail.gmail.com
Content-Type: text/plain; charset=ISO-8859-1

I don't know that netwire is more difficult to understand. I'm
appreciating the network analogy and the generalisation of wires.

Thanks for pointing it out!


Cheers,
Darren



On Tue, Sep 18, 2012 at 7:35 PM, Ertugrul S?ylemez e...@ertes.de wrote:
 Christopher Howard christopher.how...@frigidcode.com wrote:

 Which FRP framework (i.e., Haskell package) is the best one to play
 with for someone still trying to grasp the basics of FRP?

 In terms of tutorials and related blog posts I currently recommend
 reactive-banana.  In terms of power and elegance I recommend Netwire.

 The main difference is that reactive-banana is both simple and easy.  It
 implements classic FRP with the usual notion of behaviors and events.
 Heinrich strives to make it very accessible.

 Netwire follows a more algebraic path and drops the classic notion.  The
 line between signals and events is blurred.  It's a bit more difficult
 to understand, but is more expressive and concise.  Also it's pretty
 much time-leak-free.  The library is designed to be very elegant while
 preserving non-FRP performance to a high degree.

 (To be fair, I'm the author of Netwire.) =)


 Greets,
 Ertugrul

 --
 Not to be or to be and (not to be or to be and (not to be or to be and
 (not to be or to be and ... that is the list monad.

 ___
 Beginners mailing list
 Beginners@haskell.org
 http://www.haskell.org/mailman/listinfo/beginners




--

Message: 3
Date: Wed, 19 Sep 2012 13:35:32 +0700
From: Kim-Ee Yeoh k...@atamo.com
Subject: Re: [Haskell-beginners] FRP
To: Christopher Howard christopher.how...@frigidcode.com
Cc: Haskell Beginners beginners@haskell.org
Message-ID:
CAPY+ZdT55PX8=o3ja-z5nykjl_jqj-btlrpabtddjczq9gf...@mail.gmail.com
Content-Type: text/plain; charset=iso-8859-1

On Wed, Sep 19, 2012 at 4:20 AM, Christopher Howard wrote:

 Which FRP framework (i.e., Haskell package) is the best one to play with
 for someone still trying to grasp the basics of FRP?


I think of FRP as a Dream that's still being worked on.  So to get at the
basics of the Dream I do a lot of gedankenexperiment, sketching on pen and
paper, and code fragments.  I read Conal Elliott's blog to gather the
results of his investigations of that Dream.

But I understand that you're a practical kind of guy and prefers to push
and poke to learn stuff, and I think 

<    5   6   7   8   9   10   11   12   13   14   >