foldl' ?

2002-11-16 Thread Mark Carroll
Where do I find foldl' in GHC? It's mentioned on
http://www.haskell.org/ghc/docs/latest/html/base/Data.List.html but
importing List and using "-package data" don't seem to make it appear. I'm
using GHC 5.02.2. I must be making some simple mistake.

-- Mark

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: foldl' ?

2002-11-16 Thread Hal Daume III
If it appears in Data.List then you need to import Data.List.  In order to
do this, you will need a newer (>=5.03) version of GHC, if I'm not
mistaken.

 - Hal

--
Hal Daume III

 "Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume

On Sat, 16 Nov 2002, Mark Carroll wrote:

> Where do I find foldl' in GHC? It's mentioned on
> http://www.haskell.org/ghc/docs/latest/html/base/Data.List.html but
> importing List and using "-package data" don't seem to make it appear. I'm
> using GHC 5.02.2. I must be making some simple mistake.
> 
> -- Mark
> 
> ___
> Glasgow-haskell-users mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
> 

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: foldl' ?

2002-11-16 Thread Richard E . Adams
I don't know if this will help, but I am using GHC Interactive, version 
5.03, for Haskell 98, and I wanted to use the 'toUpper' function.  
'toUpper' is defined in Data.Char, but is not loaded when ghci is  
started:

 Prelude> :info toUpper

 Variable not in scope: `toUpper'

To bring 'toUpper' into scope, I put "import Char" in my program (a very 
simple program named "Text1.hs"):

 module Text1 where
 import Char

 f = Char.toUpper 'a'

After starting ghci from the operating system shell, I enter ":load 
" at the ghci prompt, then evaluate the function 'f':

 [localhost:~/Documents/myHaskellProgs] richard% ghci
  .
  .
  .
 Loading package base ... linking ... done.
 Loading package haskell98 ... linking ... done.
 Prelude> :load Text1.hs
 Compiling Text1( Text1.hs, interpreted )
 Ok, modules loaded: Text1.
 *Text1> f
 'A'
 *Text1>

Richard E. Adams
Email: [EMAIL PROTECTED]
  (or) [EMAIL PROTECTED]


On Saturday, November 16, 2002, at 06:55 AM, Mark Carroll wrote:

Where do I find foldl' in GHC? It's mentioned on
http://www.haskell.org/ghc/docs/latest/html/base/Data.List.html but
importing List and using "-package data" don't seem to make it appear. 
I'm
using GHC 5.02.2. I must be making some simple mistake.

-- Mark

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: foldl' ?

2002-11-22 Thread Mark Carroll
On Sat, 16 Nov 2002, Hal Daume III wrote:

> If it appears in Data.List then you need to import Data.List.  In order to
> do this, you will need a newer (>=5.03) version of GHC, if I'm not
> mistaken.

I find it curious that I can do:

cicero:markc$ ghci -package data
   ___ ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |  GHC Interactive, version 5.04, for Haskell 98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package base ... linking ... done.
Loading package haskell98 ... linking ... done.
Loading package lang ... linking ... done.
Loading package concurrent ... linking ... done.
Loading package posix ... linking ... done.
Loading package util ... linking ... done.
Loading package data ... linking ... done.
Prelude> :type FiniteMap.lookupFM
forall key elt.
(Ord key) =>
Data.FiniteMap.FiniteMap key elt -> key -> Maybe elt
Prelude> :type List.isSuffixOf
forall a. (Eq a) => [a] -> [a] -> Bool
Prelude> :type List.foldl'

:1: Variable not in scope: `List.foldl''
Prelude>


How come I can get at lookupFM and isSuffixOf but not foldl'? (-:

(Thanks to you and Richard for replies!)

-- Mark

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: foldl' ?

2002-11-22 Thread Hal Daume III
Because List is the H98 module, Data.List is the extended one which
contains foldl'.  Regardless of whether you say -package data or not,
you're not going to get Data.List unless you ask for it explicitly:

moussor:multidoc-sum/ ghci -package data
   ___ ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |  GHC Interactive, version 5.04.1, for Haskell
98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package base ... linking ... done.
Loading package haskell98 ... linking ... done.
Loading package lang ... linking ... done.
Loading package concurrent ... linking ... done.
Loading package posix ... linking ... done.
Loading package util ... linking ... done.
Loading package data ... linking ... done.
Prelude> :t List.foldl'

:1: Variable not in scope: `List.foldl''
Prelude> :t Data.List.foldl'
forall a b. (a -> b -> a) -> a -> [b] -> a
Prelude> 


--
Hal Daume III

 "Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume

On Fri, 22 Nov 2002, Mark Carroll wrote:

> On Sat, 16 Nov 2002, Hal Daume III wrote:
> 
> > If it appears in Data.List then you need to import Data.List.  In order to
> > do this, you will need a newer (>=5.03) version of GHC, if I'm not
> > mistaken.
> 
> I find it curious that I can do:
> 
> cicero:markc$ ghci -package data
>___ ___ _
>   / _ \ /\  /\/ __(_)
>  / /_\// /_/ / /  | |  GHC Interactive, version 5.04, for Haskell 98.
> / /_\\/ __  / /___| |  http://www.haskell.org/ghc/
> \/\/ /_/\/|_|  Type :? for help.
> 
> Loading package base ... linking ... done.
> Loading package haskell98 ... linking ... done.
> Loading package lang ... linking ... done.
> Loading package concurrent ... linking ... done.
> Loading package posix ... linking ... done.
> Loading package util ... linking ... done.
> Loading package data ... linking ... done.
> Prelude> :type FiniteMap.lookupFM
> forall key elt.
> (Ord key) =>
> Data.FiniteMap.FiniteMap key elt -> key -> Maybe elt
> Prelude> :type List.isSuffixOf
> forall a. (Eq a) => [a] -> [a] -> Bool
> Prelude> :type List.foldl'
> 
> :1: Variable not in scope: `List.foldl''
> Prelude>
> 
> 
> How come I can get at lookupFM and isSuffixOf but not foldl'? (-:
> 
> (Thanks to you and Richard for replies!)
> 
> -- Mark
> 
> ___
> Glasgow-haskell-users mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
> 

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: foldl' ?

2002-11-26 Thread Mark Carroll
On Fri, 22 Nov 2002, Hal Daume III wrote:

> Because List is the H98 module, Data.List is the extended one which
> contains foldl'.  Regardless of whether you say -package data or not,
> you're not going to get Data.List unless you ask for it explicitly:
(snip)

Thanks very much indeed! I finally have it working. (-:

-- Mark

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



foldl laziness support

2006-10-15 Thread Serge D. Mechveliani
Dear Haskell implementors,

I keep on facing a frightening problem of the laziness support.
Consider the example of

---
import List (union)

main = let n = 10^4 :: Int
   in
   putStr
   (shows (take 2 $ unionMany [[1 .. i] | i <- [1 .. n]]) "\n")

unionMany = foldl union []
---

Compiling it in   ghc-6.6,  -O, 

we have the running cost  O(n),  instead of  O(1).

Now, changing to 

  unionMany []=  []
  unionMany (xs: xss) =  union xs (unionMany xss)
,
we reach  O(1).
For example, for  n = 10^9,  the time remains less than   0.01 sec.

My program has many fragments of such kind, when a function produces
a long list, some client functions need all the list, and others need
only its small initial part.
When we rely on the standard library,  foldl  creeps in everywhere.
Also may things are easy to program via  foldl.

I wonder how to avoid these numerous cost pitfalls.
Maybe, the complier could do more optimization?

Regards,

-
Serge Mechveliani
[EMAIL PROTECTED]
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: foldl laziness support

2006-10-15 Thread Lemmih

On 10/15/06, Serge D. Mechveliani <[EMAIL PROTECTED]> wrote:

Dear Haskell implementors,

I keep on facing a frightening problem of the laziness support.
Consider the example of

---
import List (union)

main = let n = 10^4 :: Int
   in
   putStr
   (shows (take 2 $ unionMany [[1 .. i] | i <- [1 .. n]]) "\n")

unionMany = foldl union []
---

Compiling it in   ghc-6.6,  -O,

we have the running cost  O(n),  instead of  O(1).

Now, changing to

  unionMany []=  []
  unionMany (xs: xss) =  union xs (unionMany xss)
,
we reach  O(1).
For example, for  n = 10^9,  the time remains less than   0.01 sec.

My program has many fragments of such kind, when a function produces
a long list, some client functions need all the list, and others need
only its small initial part.
When we rely on the standard library,  foldl  creeps in everywhere.
Also may things are easy to program via  foldl.

I wonder how to avoid these numerous cost pitfalls.
Maybe, the complier could do more optimization?


How about using 'foldr'?

--
Cheers,
 Lemmih
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: foldl laziness support

2006-10-15 Thread Duncan Coutts
On Sun, 2006-10-15 at 18:05 +0400, Serge D. Mechveliani wrote:
> Dear Haskell implementors,
> 
> I keep on facing a frightening problem of the laziness support.

[snip]

> I wonder how to avoid these numerous cost pitfalls.
> Maybe, the complier could do more optimization?

There are important differences between foldl, foldl' and foldr. It is
quite important to choose the right one. I don't think this can be done
automagically.

In my experience, the choice is almost always between foldl' and foldr.
For lists, foldl is rarely useful (for arrays on the other hand both
foldl and foldr' are useful).

The usual rule of thumb is that if you are constructing some small
atomic value (e.g. an integer) then foldl' is the right choice. If
you're building a value that is naturally constructed and consumed
lazily (e.g. a list) then foldr is the right choice.

So as Lemmih says, in this case you want to use foldr:

---
import List (union)
main = let n = 10^4 :: Int
   in
   putStr
   (shows (take 2 $ unionMany [[1 .. i] | i <- [1 .. n]]) "\n")

unionMany = foldr union []
-------

So this is just as easy to write as the foldl(') version.

As I said, I think it'd be hard to figure out automatically when it is
desirable and safe to switch (foldl f unit) to/from (foldr (flip f)
unit). Though, perhaps it'd be possible for some analysis tool to
provide a hint to the programmer based on the strictness of the function
we are folding and the strictness in the structure of the type we are
building. If it could be done reasonably reliably then it might be
useful to help programmers to choose appropriately and avoid performance
problems.

Duncan

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: foldl laziness support

2006-10-15 Thread Bulat Ziganshin
Hello Serge,

Sunday, October 15, 2006, 6:05:43 PM, you wrote:

if i correctly understood your problem, ultimate solution is the
fusion RULES for foldl that is planned for 6.8 (there is yicket about
this). may be YOU can develop such rules? :)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


foldl laziness support. Reply

2006-10-16 Thread Serge D. Mechveliani
Concerning the laziness support problem,

I thank people for explanations about  foldl and foldr.

>> I wonder how to avoid these numerous cost pitfalls.
>> Maybe, the complier could do more optimization?


Duncan Coutts <[EMAIL PROTECTED]>  writes

> There are important differences between foldl, foldl' and foldr. It is
> quite important to choose the right one. I don't think this can be done
> automatically.
>
> In my experience, the choice is almost always between foldl' and foldr.
> 
> [..]

I do not see  foldl'  in the standard library.
Is it of the GHC lib extension?  has it strictness annotation?


> So as Lemmih says, in this case you want to use foldr:
>
> import List (union)
> main = let n = 10^4 :: Int
>in
>putStr
>(shows (take 2 $ unionMany [[1 .. i] | i <- [1 .. n]]) "\n")
>
> unionMany = foldr union []

I see. Thank you.
I have impression that something is here besides the intuition for the 
foldl/foldr choice.

Here is a contrived example which is more close to my real situation.

-
import qualified Data.Set as Set (Set(..), empty, member, insert)
import List (union, find)

main = let  n = 10^6 :: Int  in  putStr (shows (g1 n) "\n")

f :: Int -> (Set.Set Int, [Int])
fn   =  

  -- original version, I write so because it is easy to program
  --
  foldl add (Set.empty, []) [[1 .. i] | i <- [1 .. n]]
  where
  add (s, xs) ys =  (Set.insert (sum xs) s, union xs ys)

  {- attempt to optimize (fails)
  --
  h (Set.empty, []) [[1 .. i] | i <- [1 .. n]]
  where
  h (s, xs) []= (s, xs) 
  h (s, xs) (ys: yss) = h (Set.insert (sum xs) s, union xs ys) yss
  -}

g1, g2 :: Int -> Bool -- client functions

g1 n = case  snd $ f n  of  x: _ -> even x
_-> False

g2 n = let (set, xs) = f n
   in
   case  find (> 100) xs  of  Just x -> Set.member (2*x) set
  _  -> False
-

Evidently,  g1 n  must have the cost of  O(1).  
But in  ghc-6.6 -O,  it has O(n).

How to improve  f ?  I tried  foldr,  and failed.

The situation is so that some clients are as  g1,  and others are as  
g2, and, at least,  g1  must be O(1).

Regards,

-
Serge Mechveliani
[EMAIL PROTECTED]
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: foldl laziness support. Reply

2006-10-16 Thread Duncan Coutts
On Mon, 2006-10-16 at 14:23 +0400, Serge D. Mechveliani wrote:
> Concerning the laziness support problem,
> 
> I thank people for explanations about  foldl and foldr.
> 
> >> I wonder how to avoid these numerous cost pitfalls.
> >> Maybe, the complier could do more optimization?
> 
> 
> Duncan Coutts <[EMAIL PROTECTED]>  writes
> 
> > There are important differences between foldl, foldl' and foldr. It is
> > quite important to choose the right one. I don't think this can be done
> > automatically.
> >
> > In my experience, the choice is almost always between foldl' and foldr.
> > 
> > [..]
> 
> I do not see  foldl'  in the standard library.
> Is it of the GHC lib extension?  has it strictness annotation?

It's in the standard Data.List module. It's not in the Prelude.

Duncan

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: foldl laziness support. Reply

2006-10-16 Thread Neil Mitchell

Hi


I do not see  foldl'  in the standard library.
Is it of the GHC lib extension?  has it strictness annotation?


Hoogle it!

http://haskell.org/hoogle/?q=foldl%27

Data.List.foldl' :: (a -> b -> a) -> a -> [b] -> a

Thanks

Neil
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: foldl laziness support. Reply

2006-10-17 Thread roconnor
Although this doesn't answer your question, I think it is releated.  When 
implementing SHA, I need to create a recursive function to append the 
length of a string to the string.  This function needed to be strict, 
because it needed to accumulted the length of the string, and it needed to 
be lazy, because it needed to re-emmit the characters that it consumed.


I have a short discussion about this at 
.


--
Russell O'Connor  
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users