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. Fwd: [Haskell-beginners] combinatorial (Patrick LeBoutillier)
   2. Re:  combinatorial (Michael Mossey)
   3. Re:  Important coding guideline and library       proposal
      (a...@spamcop.net)
   4.  FFI and Cabal (Jeffrey Drake)
   5.  Retrieving the decimal portion of a Double (Dominic Sim)
   6. Re:  Retrieving the decimal portion of a Double (Shawn Willden)
   7.  recommended way to get haskell 6.10 installed on ubuntu
      hardy? (Joe Van Dyk)
   8. Re:  recommended way to get haskell 6.10 installed        on      ubuntu
      hardy? (Tony Morris)


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

Message: 1
Date: Sun, 22 Nov 2009 17:04:11 -0500
From: Patrick LeBoutillier <patrick.leboutill...@gmail.com>
Subject: Fwd: [Haskell-beginners] combinatorial
To: beginners <beginners@haskell.org>
Message-ID:
        <b217a64f0911221404g118e9281t57e5222bd6c44...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Forgot to forward my response to the list...

---------- Forwarded message ----------
From: Patrick LeBoutillier <patrick.leboutill...@gmail.com>
Date: Sun, Nov 22, 2009 at 5:03 PM
Subject: Re: [Haskell-beginners] combinatorial
To: "Michael P. Mossey" <m...@alumni.caltech.edu>


Michael,

Here's how I would go about this:


type MidiPitch = Int

range :: [MidiPitch]
range = [10..90]

-- Just a dummy eval function, allows up or down one unit
eval ps | length ps <= 1 = Just 1.0
eval ps | length ps > 1  =
 let a = last ps
     b = last . init $ ps in
 if abs (a - b) == 1
    then Just 1.0
    else Nothing

coolFunc :: Int -> MidiPitch -> ([MidiPitch] -> Maybe Float) -> [[MidiPitch]]
coolFunc n p f = generate n f [[p]]

-- Generate MidiPitch lists up to a given length, making sure each step
-- satisfies the eval function
generate :: Int -> ([MidiPitch] -> Maybe Float) -> [[MidiPitch]] ->
[[MidiPitch]]
generate n f cs | n == 1 = cs
generate n f cs = generate (n-1) f $ concat . map (\p -> try p cs) $ range

-- Tries to add a MidiPitch to each of the MidiPitch lists, keep
-- only the sequences that pass the eval.
try :: MidiPitch -> [[MidiPitch]] -> [[MidiPitch]]
try p = filter (not . null) . map (test p)
 where test p ps =
         let ps' = ps ++ [p] in
         case eval ps' of
           Nothing   -> []
           otherwise -> ps'


It's seems to work, although I'm sure many bits sould be made more elegant...

Note: After that another pass would be required over the result set to
find the sequences that have the highest scores.


Patrick


On Sun, Nov 22, 2009 at 5:25 AM, Michael P. Mossey
<m...@alumni.caltech.edu> wrote:
> I'm trying to write a combinatorial search algorithm with evaluation, and
> kind of stuck. Not sure how to do this.
>
> I'm constructing a musical phrase, which is a list of MidiPitch:
>
> [MidiPitch]
>
> I have an evaluation function that determines the fitness of any given
> phrase:
>
> eval :: [MidiPitch] -> Maybe Float
>
> This returns Nothing if the phrase is completely unacceptable.
>
> The idea is to build up a phrase one midi pitch at a time, choosing all
> possible next pitches (notes) from a range:
>
> next pitch comes from: [10..90]
>
> Most of the pitches will result in a phrase that evaluates to Nothing, so
> the combinatoral "explosion" will be limited.
>
> I'd like to write a function that constructs a phrase of length n, and in
> fact will have to return a list of all phrases that have equal scores of the
> maximum.
>
> --         <length of output phrase> -> <first pitch> -> <eval func> ->
> --         <all tied phrases of best score>
> coolFunc :: Int -> MidiPitch -> ([MidiPitch] -> Maybe Float) ->
>           [[MidiPitch]]
>
> I am stuck on how to write this.
>
> thanks,
> Mike
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



--
=====================
Patrick LeBoutillier
Rosemère, Québec, Canada



-- 
=====================
Patrick LeBoutillier
Rosemère, Québec, Canada


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

Message: 2
Date: Sun, 22 Nov 2009 14:30:57 -0800
From: Michael Mossey <m...@alumni.caltech.edu>
Subject: Re: [Haskell-beginners] combinatorial
To: "Edward Z. Yang" <ezy...@mit.edu>
Cc: beginners <beginners@haskell.org>
Message-ID: <4b09bba1.2040...@alumni.caltech.edu>
Content-Type: text/plain; charset=UTF-8; format=flowed



Edward Z. Yang wrote:
> We can relax this requirement by returning a list of all phrases that
> are of length n (and were not unacceptable) and then doing some kind
> of fold.  

Thanks for the advice and code.

> Note that since your evaluation function is not incremental
> (i.e. I can't pass it a partial evaluation) I don't maintain scores
> in workFunc.

I'm not totally exactly sure what you mean here, but my evaluation function 
can in fact evaluate phrases of any length.

In fact, I realized after seeing your reply that I failed to describe my 
problem well at all.

Here's what I had in mind for a search algorithm. The idea is to combine 
features of greedy and broad search. I have no idea is this is a good idea. 
It's just a thought.

Let's say we start by evaluating all lists of length 2 and picking those 
tied for the maximum score. Then the algorithm is,

   for each input list of length 2 tied for maximum,
      make all lists of length 3 that are acceptable (that don't return
      Nothing when evaluated)
   concat all those
   evaluate all of them and pick all tied for the maximum
   feed into next step  (continue with lengths 4..N.)

The idea is that's a greedy algorithm that still allows for some breadth of 
search by looking at ties. In my scoring system there will often be ties.

Thanks,
Mike



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

Message: 3
Date: Sun, 22 Nov 2009 21:54:10 -0500
From: a...@spamcop.net
Subject: Re: [Haskell-beginners] Important coding guideline and
        library proposal
To: beginners@haskell.org
Message-ID: <20091122215410.aqwbhyiog2sc44cc-...@webmail.spamcop.net>
Content-Type: text/plain;       charset=ISO-8859-1;     DelSp="Yes";
        format="flowed"

G'day all.

Quoting Daniel Fischer <daniel.is.fisc...@web.de>:

> Proposal:
> rename 'length' to   
> 'yesIReallyWantToKnowTheExactLengthOfThisListSoPleaseCalculateItForMe'
> to reduce performance bugs caused by naive uses of length.

genericYesIReallyWantToKnowTheExactLengthOfThisListSoPleaseCalculateItForMe

Another option is to rename Data.List to Data.List.YesIKnowThisIsNotAnArray.

Cheers,
Andrew Bromage


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

Message: 4
Date: Mon, 23 Nov 2009 02:35:00 -0500
From: Jeffrey Drake <iae...@me.com>
Subject: [Haskell-beginners] FFI and Cabal
To: "beginners@haskell.org Beginners Haskell" <beginners@haskell.org>
Message-ID: <91887885400682927252573119286481217153-webm...@me.com>
Content-Type: text/plain; charset=ISO-8859-1


I am trying to use FFI to access some windows console functions via two simple 
C functions I created.

Essentially my module looks like is this: 

{-# CFILES mouse.c #-}
{-# LANGUAGE ForeignFunctionInterface #-}
module Mouse where 
-- import Foreign
import Foreign.C.Types


foreign import ccall unsafe "mouse.h SetupConsole" c_setupConsole :: IO CInt
foreign import ccall unsafe "mouse.h MouseEvent" c_mouseEvent :: IO CInt

setupConsole :: IO Bool
setupConsole = do   c <- c_setupConsole
                    return $ if c == 0
                        then True
                        else False

mouseEvent :: IO (Maybe (Int, Int))
mouseEvent = do c <- c_mouseEvent
                let d = toInteger c
                let e = (fromInteger d)::Int
                
                return $ if e < 0
                    then Nothing
                    else Just (e `mod` 256, e `div` 256)


It seems to compile fine. The problem comes when I need to link.
Linking dist\build\BoardGames\BoardGames.exe ...
dist\build\BoardGames\BoardGames-tmp\Mouse.o:fake:(.text+0x15): undefined 
reference to `SetupConsole'
dist\build\BoardGames\BoardGames-tmp\Mouse.o:fake:(.text+0x11d): undefined 
reference to `MouseEvent'
collect2: ld returned 1 exit status

The problem seems obvious - it isn't compiling OR linking mouse.c which is this:

#include <windows.h>

int SetupConsole()
{
    HANDLE hStdin; 
    DWORD fdwMode, fdwSaveOldMode; 
    int counter=0;
 
    
    hStdin = GetStdHandle(((DWORD)-10)); 
    if (hStdin == ((HANDLE)(LONG_PTR)-1)) 
        return -3; 
 
    
 
    if (! GetConsoleMode(hStdin, &fdwSaveOldMode) ) 
        return -2;
 
    
 
    fdwMode = 0x0010; 
    if (! SetConsoleMode(hStdin, fdwMode) ) 
        return -1;
        return 0;
}

int MouseEvent()
{
        HANDLE hStdin;
        INPUT_RECORD irInBuf[128];
        short x, y;
        unsigned i;
        DWORD cNumRead;

        static int ignoreNext = 0;


        hStdin = GetStdHandle(((DWORD)-10)); 
    if (hStdin == ((HANDLE)(LONG_PTR)-1)) 
                return -2;

        if (!ReadConsoleInputW( 
              hStdin,      
                irInBuf,     
                128,         
                &cNumRead) ) 
            return -1;

   for (i = 0; i < cNumRead; i++) 
        {
                        if (irInBuf[i].EventType == 0x0002 && 
irInBuf[i].Event.MouseEvent.dwEventFlags == 0)
                        {
                                if (ignoreNext == 1)
                                {
                                        ignoreNext = 0;
                                        return -1;
                                }
                                x = 
irInBuf[i].Event.MouseEvent.dwMousePosition.X;
                                y = 
irInBuf[i].Event.MouseEvent.dwMousePosition.Y;

                                ignoreNext = 1;

                                return x + (y << 8);
                        }
                        else
                        {
                                continue;
                        }
   }
   return -1;
}

So far, I have only tested this with MSVC (it works), but not with haskell 
platform's mingw (which includes windows.h - so I would have to wait for 
this...)

In my cabal file I have:
 c-sources:             mouse.c

So that basically sums up what I have, I just don't know how to do this. The 
cabal documentation says for this directive:

c-sources: filename list
A list of C source files to be compiled and linked with the Haskell files.

Which is what I expected it to do - but to no avail.

I should note that when I try to comment out with -- the c-sources line I get 
this:

Linking dist\build\BoardGames\BoardGames.exe ...
dist\build\BoardGames\BoardGames-tmp\Main.o:fake:(.text+0x27d): undefined 
reference to `__stginit_Mouse_'
dist\build\BoardGames\BoardGames-tmp\Main.o:fake:(.text+0xb4): undefined 
reference to `Mouse_a1_info'
dist\build\BoardGames\BoardGames-tmp\Main.o:fake:(.text+0xcc): undefined 
reference to `Mouse_czusetupConsole_info'
dist\build\BoardGames\BoardGames-tmp\Main.o:fake:(.text+0xf8): undefined 
reference to `Mouse_a1_info'
dist\build\BoardGames\BoardGames-tmp\Main.o:fake:(.text+0x17a): undefined 
reference to `Mouse_czusetupConsole_info'
dist\build\BoardGames\BoardGames-tmp\Main.o:fake:(.data+0x14): undefined 
reference to `Mouse_a1_closure'
collect2: ld returned 1 exit status


Any help that can be offered would be appreciated.

I would tell you where to find the project, but patch-tag is being unavailable 
for me at this time. It is the 'BoardGames' project, under iaefai.

Thank you again,
iaefai.


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

Message: 5
Date: Mon, 23 Nov 2009 06:31:05 -0800 (PST)
From: Dominic Sim <dskw...@yahoo.com>
Subject: [Haskell-beginners] Retrieving the decimal portion of a
        Double
To: beginners@haskell.org
Message-ID: <226442.15547...@web34506.mail.mud.yahoo.com>
Content-Type: text/plain; charset="iso-8859-1"

    Hi all,

    I am trying to retrieve the decimal portion of a Double. My code is:

    getDecimal x = x - floor(x)

    I would expect the following:

    Main> getDecimal 1.23
    0.23 :: [Double]

    but instead, I get:

    Main> getDecimal 1.23
    ERROR - Unresolved overloading
    *** Type       : (RealFrac a, Integral a) => a
    *** Expression : getDecimal 1.23

    I have tried adding "getDecimal :: Double -> Double" but it only causes the 
following message to appear:

    ERROR file:C:\Documents and Settings\User\file.hs:60 - Instance of Integral 
Double required for definition of getDecimal

    How should I define my function so that it'll work? Thanks!

    Regards,
    Dom



      
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20091123/1ce2a1dc/attachment-0001.html

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

Message: 6
Date: Mon, 23 Nov 2009 08:45:00 -0700
From: Shawn Willden <shawn-hask...@willden.org>
Subject: Re: [Haskell-beginners] Retrieving the decimal portion of a
        Double
To: beginners@haskell.org
Message-ID: <200911230845.00819.shawn-hask...@willden.org>
Content-Type: text/plain;  charset="utf-8"

On Monday 23 November 2009 07:31:05 am Dominic Sim wrote:
>     I am trying to retrieve the decimal portion of a Double. My code is:
>
>     getDecimal x = x - floor(x)

The problem is that x is a double (or some other kind of floating point or 
fraction), and "floor x" is an integer, and you can't subtract an integer 
from a double.  To convert "floor x" to a double (or to any other relevant 
type), use "fromIntegral", like:

        getDecimal x = x - fromIntegral(floor x)

However, what I'd really suggest is that you use:

        getDecimal x = snd (properFraction x)

or, in pointfree style:

        getDecimal = snd . properFraction

Also, the type signature for getDecimal should be:

        getDecimal :: RealFrac a => a -> a

That will allow it to be used with any Real or Fractional type.

        Shawn.



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

Message: 7
Date: Mon, 23 Nov 2009 12:08:46 -0800
From: Joe Van Dyk <j...@fixieconsulting.com>
Subject: [Haskell-beginners] recommended way to get haskell 6.10
        installed on    ubuntu hardy?
To: beginners@haskell.org
Message-ID:
        <c715e640911231208w6cbc061dh58a74a530d532...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

There's no ubuntu package for 6.10 (only 6.8), and the haskell
platform says you need 6.10 installed to build the source package.



-- 
Joe Van Dyk
http://fixieconsulting.com


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

Message: 8
Date: Tue, 24 Nov 2009 06:12:23 +1000
From: Tony Morris <tonymor...@gmail.com>
Subject: Re: [Haskell-beginners] recommended way to get haskell 6.10
        installed       on      ubuntu hardy?
To: Joe Van Dyk <j...@fixieconsulting.com>
Cc: beginners@haskell.org
Message-ID: <4b0aeca7.2080...@gmail.com>
Content-Type: text/plain; charset=UTF-8

Hi Joe,
You might consider installing the 6.8 package to bootstrap a 6.10
compile. I've done it a few times with high success and pretty
straight-forward.

Joe Van Dyk wrote:
> There's no ubuntu package for 6.10 (only 6.8), and the haskell
> platform says you need 6.10 installed to build the source package.
>
>
>
>   

-- 
Tony Morris
http://tmorris.net/




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

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


End of Beginners Digest, Vol 17, Issue 27
*****************************************

Reply via email to