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
        [EMAIL PROTECTED]

You can reach the person managing the list at
        [EMAIL PROTECTED]

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


Today's Topics:

   1.  gtk2hs not rendering drawingArea (Norbert Wojtowicz)
   2. RE:  Profiling haskell code (Sayali Kulkarni)
   3.  getRecursiveContents - example from `Real World  Haskell'
      (Johann Giwer)
   4. Re:  gtk2hs not rendering drawingArea (Johann Giwer)
   5. Re:  Profiling haskell code (Brent Yorgey)
   6.  Useful set of -W switches for .ghci? (?????????? ?. ????????)
   7. Re:  Useful set of -W switches for .ghci? (Daniel Fischer)
   8. Re:  Useful set of -W switches for .ghci? (?????????? ?. ????????)


----------------------------------------------------------------------

Message: 1
Date: Thu, 4 Dec 2008 13:07:06 +0100
From: "Norbert Wojtowicz" <[EMAIL PROTECTED]>
Subject: [Haskell-beginners] gtk2hs not rendering drawingArea
To: beginners@haskell.org
Message-ID:
        <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=ISO-8859-1

Hello,

I'm having problems getting a drawingArea to render, I've narrowed the
program down to the following skeleton. Any suggestions on what I'm
doing wrong? The label gets updated correctly, but the drawingArea
just remains gray as if it was never rendered. I'm including an entire
compilable skeleton in case someone wants to help me debug it. (I have
a feeling I'm just missing something very obvious...)

Thanks in advance,
Norbert

skeletonTest.hs:

module Main where
import Graphics.UI.Gtk -- hiding (fill)
import Graphics.UI.Gtk.Glade
import Graphics.Rendering.Cairo.SVG
import Graphics.Rendering.Cairo
import Control.Monad

main = do
  initGUI
  let gFile = "brainSpin.glade"
  windowXmlM <- xmlNew gFile
  let windowXml = case windowXmlM of
                    (Just windowXml) -> windowXml
                    Nothing -> error "Can't find the glade file
\"brainSpin.glade\" in the current directory"
  window <- xmlGetWidget windowXml castToWindow "brainSpinMain"
  onDestroy window mainQuit
  label <- xmlGetWidget windowXml castToLabel "label1"
  drawArea <- xmlGetWidget windowXml castToDrawingArea "drawArea"
  widgetShowAll window
  labelSetText label "foo"

  -- THIS is the offending code. Originally I was working with SVGs,
but I simplified
  -- it to this, just to track down the problem. It seems any Render () does not
  -- get updated in the drawArea
  let r = do setSourceRGB 0 0 0
             paint
  drawin <- widgetGetDrawWindow drawArea
  renderWithDrawable drawin r

  mainGUI


brainSpin.glade:

<?xml version="1.0" encoding="UTF-8" standalone="no"?>
<!DOCTYPE glade-interface SYSTEM "glade-2.0.dtd">
<!--Generated with glade3 3.4.5 on Thu Dec  4 12:50:25 2008 -->
<glade-interface>
  <widget class="GtkWindow" id="brainSpinMain">
    <child>
      <widget class="GtkVBox" id="vbox1">
        <property name="visible">True</property>
        <child>
          <widget class="GtkLabel" id="label1">
            <property name="visible">True</property>
            <property name="label" translatable="yes">label</property>
          </widget>
        </child>
        <child>
          <widget class="GtkDrawingArea" id="drawArea">
            <property name="visible">True</property>
          </widget>
          <packing>
            <property name="position">1</property>
          </packing>
        </child>
      </widget>
    </child>
  </widget>
</glade-interface>


------------------------------

Message: 2
Date: Thu, 4 Dec 2008 17:42:42 +0530
From: "Sayali Kulkarni" <[EMAIL PROTECTED]>
Subject: RE: [Haskell-beginners] Profiling haskell code
To: "Brent Yorgey" <[EMAIL PROTECTED]>
Cc: beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain;       charset="us-ascii"

Hey thanks Brent. This helped.

I have one more question now.

Consider I have two functions 
1. gives me a range of numbers in an array.
2. has to get an array input for further process.

Then how can I get the array generated by the first function tobe the
input of the second function?

Regards,
Sayali

-----Original Message-----
From: Brent Yorgey [mailto:[EMAIL PROTECTED] 
Sent: Tuesday, November 18, 2008 5:47 PM
To: Sayali Kulkarni
Subject: Re: [Haskell-beginners] Profiling haskell code

> I have just given it any random input array to be sorted.
> The commands that I had sent earlier were tried on Cygwin...
> (
> > > $ ghc --make Project.hs -prof -auto-all
> > >  
> > >  
> > > $ Project +RTS -p
> > >  ) 

This ought to work fine.  Just a note, to do any reasonable profiling
you will need to give it a *much* larger list to sort.  Otherwise it
will
execute so quickly that the timing data you get will be meaningless.

> 
> Also can you tell me any other method for profiling the code that you
> know? 

If you just want to see how long it takes to evaluate certain
expressions, you can type ':set +s' in ghci; from then on after every
expression you type it will tell you how long it took to evaluate and
how much memory was used.

-Brent


------------------------------

Message: 3
Date: Fri, 5 Dec 2008 12:14:07 +0100
From: Johann Giwer <[EMAIL PROTECTED]>
Subject: [Haskell-beginners] getRecursiveContents - example from `Real
        World   Haskell'
To: The Haskell-Beginners Mailing List <beginners@haskell.org>
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=us-ascii

`Real World Haskell' is a great book. I really love it. When I tried an example
from the 9th Chapter, I was a bit disappointed:

*Main> f <- getRecursiveContents "/home/johann/"
Heap exhausted;
Current maximum heap size is 128000000 bytes (122 Mb);
use `+RTS -M<size>' to increase it.

The function lookes like this:

getRecursiveContents :: FilePath -> IO [FilePath]
getRecursiveContents topdir = do
  names <- getDirectoryContents topdir
  let properNames = filter (`notElem` [".", ".."]) names
  paths <- forM properNames $ \name -> do                                -- 1
    let path = topdir </> name
    isDirectory <- doesDirectoryExist path
    if isDirectory
      then getRecursiveContents path
      else return [path]
  return (concat paths)                                                  -- 2

OK, I'm using a small machine and my home directory contains ~30,000 files. But
that couldn't be the real problem. And even if this function is a small example
it should work reliable.
The programming language I know best (and this is meant relative -- I'm only a
`would be programmer') is python. Python has good support for functional
programming, but no builtin tail recursion. So my first idea about the bug in
`getRecursiveContents' went in this direction. Two hours later I had worked out
this solution:

getRecursiveContents :: FilePath -> IO [FilePath]
getRecursiveContents = getRecursiveContents' [] 
  where
    getRecursiveContents' l p =
      E.handle (\_ -> return (p:l)) $ do                                 -- 3
        c <- getDirectoryContents p  
        let c' = filter (`notElem` [".", ".."]) c 
        x <- foldM (\l' p' -> getRecursiveContents' l' (p </> p')) l c'  -- 4
        return (x)

Folding (4) and appending (3) would give less memory usage than mapping (1) and
concatenation (2), I thought. This function worked well for small directory
(for which the original one did, too). But tested with my home directory it
went into an infinite loop.  That led me to the actually problem:
`doesDirectoryExist' also accepts symlinks to directories. Another hour later
this was fixed:

getRecursiveContents :: FilePath -> IO [FilePath]
getRecursiveContents = getRecursiveContents' [] 
  where
    getRecursiveContents' l p = do
      s <- getSymbolicLinkStatus p                                    
      if isDirectory s
        then 
          E.handle (\_ -> return (p:l)) $ do
            c <- getDirectoryContents p  
            let c' = filter (`notElem` [".", ".."]) c
            x <- foldM (\l' p' -> getRecursiveContents' l' (p </> p')) l c'
            return (x)
        else 
          return (p:l) 

Finally I fixed the original function (this only took about 30 min :-). The
handle (5) catches errors caused by unreadable directories

getRecursiveContents :: FilePath -> IO [FilePath]
getRecursiveContents topdir = E.handle (\_ ->return [topdir]) $ do       -- 5
  names <- getDirectoryContents topdir
  let properNames = filter (`notElem` [".", ".."]) names
  paths <- forM properNames $ \name -> do
    let path = topdir </> name
    s <- getSymbolicLinkStatus path
    if isDirectory s
      then getRecursiveContents path
      else return [path]
  return (concat paths)

The imports for all functions mentioned above are:

import Control.Monad ( forM, filterM, foldM )
import qualified Control.Exception as E
import System.Directory (doesDirectoryExist, getDirectoryContents)
import System.FilePath ((</>))
import System.Posix (getSymbolicLinkStatus, isDirectory)


Any suggestions about this solution are welcome.  

Johann




------------------------------

Message: 4
Date: Fri, 5 Dec 2008 13:07:57 +0100
From: Johann Giwer <[EMAIL PROTECTED]>
Subject: Re: [Haskell-beginners] gtk2hs not rendering drawingArea
To: The Haskell-Beginners Mailing List <beginners@haskell.org>
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=us-ascii

On Thu, Dec 04, 2008 at 01:07:06PM +0100, Norbert Wojtowicz wrote:
> Hello,
> 
> I'm having problems getting a drawingArea to render, I've narrowed the
> program down to the following skeleton. Any suggestions on what I'm
> doing wrong? The label gets updated correctly, but the drawingArea
> just remains gray as if it was never rendered. I'm including an entire
> compilable skeleton in case someone wants to help me debug it. (I have
> a feeling I'm just missing something very obvious...)
> 
> Thanks in advance,
> Norbert
> 
> skeletonTest.hs:
> 
> module Main where
> import Graphics.UI.Gtk -- hiding (fill)
> import Graphics.UI.Gtk.Glade
> import Graphics.Rendering.Cairo.SVG
> import Graphics.Rendering.Cairo
> import Control.Monad
> 
> main = do
>   initGUI
>   let gFile = "brainSpin.glade"
>   windowXmlM <- xmlNew gFile
>   let windowXml = case windowXmlM of
>                     (Just windowXml) -> windowXml
>                     Nothing -> error "Can't find the glade file
> \"brainSpin.glade\" in the current directory"
>   window <- xmlGetWidget windowXml castToWindow "brainSpinMain"
>   onDestroy window mainQuit
>   label <- xmlGetWidget windowXml castToLabel "label1"
>   drawArea <- xmlGetWidget windowXml castToDrawingArea "drawArea"
>   widgetShowAll window
>   labelSetText label "foo"
> 
>   -- THIS is the offending code. Originally I was working with SVGs,
> but I simplified
>   -- it to this, just to track down the problem. It seems any Render () does 
> not
>   -- get updated in the drawArea
>   let r = do setSourceRGB 0 0 0
>              paint
>   drawin <- widgetGetDrawWindow drawArea
>   renderWithDrawable drawin r
> 
>   mainGUI


Drawing must be done when the widget is exposed. The changes in the
code below are mainly taken from demo/svg/SvgViewer.hs.
 
main = do

  svg <- svgNewFromFile "/path/to/svg/file" 
  let (width, height) = svgGetSize svg

  initGUI
  let gFile = "brainSpin.glade"
  windowXmlM <- xmlNew gFile
  let windowXml = case windowXmlM of
                    (Just windowXml) -> windowXml
                    Nothing -> error "Can't find the glade file 
\"brainSpin.glade\" in the current directory"
  window <- xmlGetWidget windowXml castToWindow "brainSpinMain"
  onDestroy window mainQuit
  label <- xmlGetWidget windowXml castToLabel "label1"
  drawArea <- xmlGetWidget windowXml castToDrawingArea "drawArea"
  -- Here we go 
  onSizeRequest drawArea $ return (Requisition width height)
  onExpose drawArea $ updateCanvas drawArea svg

  widgetShowAll window
  labelSetText label "foo"

  mainGUI


updateCanvas :: DrawingArea -> SVG -> Event -> IO Bool
updateCanvas canvas svg (Expose { eventArea=rect }) = do
  drawin <- widgetGetDrawWindow canvas
  let (width, height) = svgGetSize svg
  (width', height') <- widgetGetSize canvas
  renderWithDrawable drawin $ do
    scale (realToFrac width'  / realToFrac width)
          (realToFrac height' / realToFrac height)
    svgRender svg
  return True

Hope, that's what you expected.

-Johann


------------------------------

Message: 5
Date: Fri, 5 Dec 2008 08:24:26 -0500
From: Brent Yorgey <[EMAIL PROTECTED]>
Subject: Re: [Haskell-beginners] Profiling haskell code
To: beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=us-ascii

To get the output of one function to be the input to another, you just
apply one to the other.  For example:

  -- This function generates a list
  foo :: Int -> [Int]
  foo n = [1..n]

  -- This function expects a list as input
  bar :: [Int] -> Int
  bar = sum . filter (>5)

  -- Use the output of foo as input to bar
  main = print $ bar (foo 20)

Are you asking about something more than this?

-Brent

On Thu, Dec 04, 2008 at 05:42:42PM +0530, Sayali Kulkarni wrote:
> Hey thanks Brent. This helped.
> 
> I have one more question now.
> 
> Consider I have two functions 
> 1. gives me a range of numbers in an array.
> 2. has to get an array input for further process.
> 
> Then how can I get the array generated by the first function tobe the
> input of the second function?
> 
> Regards,
> Sayali
> 
> -----Original Message-----
> From: Brent Yorgey [mailto:[EMAIL PROTECTED] 
> Sent: Tuesday, November 18, 2008 5:47 PM
> To: Sayali Kulkarni
> Subject: Re: [Haskell-beginners] Profiling haskell code
> 
> > I have just given it any random input array to be sorted.
> > The commands that I had sent earlier were tried on Cygwin...
> > (
> > > > $ ghc --make Project.hs -prof -auto-all
> > > >  
> > > >  
> > > > $ Project +RTS -p
> > > >  ) 
> 
> This ought to work fine.  Just a note, to do any reasonable profiling
> you will need to give it a *much* larger list to sort.  Otherwise it
> will
> execute so quickly that the timing data you get will be meaningless.
> 
> > 
> > Also can you tell me any other method for profiling the code that you
> > know? 
> 
> If you just want to see how long it takes to evaluate certain
> expressions, you can type ':set +s' in ghci; from then on after every
> expression you type it will tell you how long it took to evaluate and
> how much memory was used.
> 
> -Brent
> 


------------------------------

Message: 6
Date: Fri, 5 Dec 2008 19:03:33 +0100
From: ?????????? ?. ????????    <[EMAIL PROTECTED]>
Subject: [Haskell-beginners] Useful set of -W switches for .ghci?
To: beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; charset="utf-8"

Hey list,

I'm currently using :set -Wall in my .ghci to enforce some good coding practices
on my side. Something like missing type signatures and the like. It has saved me
quite a lot of hassle over the last couple of days as I experimented more with
Haskell. But it seems, -Wall may be just a little too… overzealous:

Prelude> 2^2

    Warning: Defaulting the following constraint(s) to type `Integer'
             `Num t' arising from a use of `^' at <interactive>:1:0-2

    Warning: Defaulting the following constraint(s) to type `Integer'
             `Integral t' arising from a use of `^' at <interactive>:1:0-2

    Warning: Defaulting the following constraint(s) to type `Integer'
             `Num t' arising from a use of `^' at <interactive>:1:0-2

    Warning: Defaulting the following constraint(s) to type `Integer'
             `Integral t' arising from a use of `^' at <interactive>:1:0-2
4

(I've shortened ghci's response a bit)

So, do you have a good (recommended) set of -W switches for a newbie playing
around in GHCi, so I can learn a good style? Forgive me if it's somewhere on
page one of some book or tutorials - I've read so many of both, I'm beginning to
forget things.

Thanks,
Aleks
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 197 bytes
Desc: not available
Url : 
http://www.haskell.org/pipermail/beginners/attachments/20081205/6b8ef7aa/attachment-0001.bin

------------------------------

Message: 7
Date: Fri, 5 Dec 2008 19:58:07 +0100
From: Daniel Fischer <[EMAIL PROTECTED]>
Subject: Re: [Haskell-beginners] Useful set of -W switches for .ghci?
To: ?????????? ?. ????????      <[EMAIL PROTECTED]>, beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain;  charset="utf-8"

Am Freitag, 5. Dezember 2008 19:03 schrieb Александър Л. 
Димитров:
> Hey list,
>
> I'm currently using :set -Wall in my .ghci to enforce some good coding
> practices on my side. Something like missing type signatures and the like.
> It has saved me quite a lot of hassle over the last couple of days as I
> experimented more with Haskell. But it seems, -Wall may be just a little
> too… overzealous:
>
> Prelude> 2^2
>
>     Warning: Defaulting the following constraint(s) to type `Integer'
>              `Num t' arising from a use of `^' at <interactive>:1:0-2
>
>     Warning: Defaulting the following constraint(s) to type `Integer'
>              `Integral t' arising from a use of `^' at <interactive>:1:0-2
>
>     Warning: Defaulting the following constraint(s) to type `Integer'
>              `Num t' arising from a use of `^' at <interactive>:1:0-2
>
>     Warning: Defaulting the following constraint(s) to type `Integer'
>              `Integral t' arising from a use of `^' at <interactive>:1:0-2
> 4
>
> (I've shortened ghci's response a bit)
>
> So, do you have a good (recommended) set of -W switches for a newbie
> playing around in GHCi, so I can learn a good style? Forgive me if it's
> somewhere on page one of some book or tutorials - I've read so many of
> both, I'm beginning to forget things.
>

Turn off those warnings you don't want, like

$ ghci -Wall -fno-warn-type-defaults
GHCi, version 6.8.3: http://www.haskell.org/ghc/  :? for help
Loading package base ... linking ... done.
Prelude> 2^2
4

A list of warning options is in section 5.7 of the user's guide (unless it's 
moved in the 6.10 branch).

> Thanks,
> Aleks

Cheers,
Daniel



------------------------------

Message: 8
Date: Sat, 6 Dec 2008 00:06:50 +0100
From: ?????????? ?. ????????    <[EMAIL PROTECTED]>
Subject: Re: [Haskell-beginners] Useful set of -W switches for .ghci?
To: Daniel Fischer <[EMAIL PROTECTED]>
Cc: beginners@haskell.org
Message-ID: <[EMAIL PROTECTED]>
Content-Type: text/plain; charset="us-ascii"

Also Sprach Daniel Fischer:
> Turn off those warnings you don't want, like
> 
> $ ghci -Wall -fno-warn-type-defaults
> GHCi, version 6.8.3: http://www.haskell.org/ghc/  :? for help
> Loading package base ... linking ... done.
> Prelude> 2^2
> 4
> 
> A list of warning options is in section 5.7 of the user's guide (unless it's 
> moved in the 6.10 branch).

Thanks very much, the location seems to be the same,
Aleks
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 197 bytes
Desc: not available
Url : 
http://www.haskell.org/pipermail/beginners/attachments/20081206/141af60b/attachment.bin

------------------------------

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


End of Beginners Digest, Vol 6, Issue 2
***************************************

Reply via email to