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:  Multiple type numeric data (David Virebayre)
   2. Re:  I have created an ugly Haskell program.. (Michael Mossey)
   3. Re:  I have created an ugly Haskell program.. (Philip Scott)
   4. Re:  I have created an ugly Haskell program.. (Michael Mossey)
   5. Re:  Error Handling and case statements (Daniel Fischer)
   6. Re:  I have created an ugly Haskell program.. (Brent Yorgey)
   7.  Finding documentation when Hackage is down. (aditya siram)
   8. Re:  Finding documentation when Hackage is down. (Michael Lesniak)


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

Message: 1
Date: Mon, 2 Nov 2009 10:51:43 +0100
From: David Virebayre <dav.vire+hask...@gmail.com>
Subject: Re: [Haskell-beginners] Multiple type numeric data
To: beginners@haskell.org
Message-ID:
        <4c88418c0911020151m678519dbv2231373544c94...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

2009/11/2 David Virebayre <dav.vire+hask...@gmail.com>:

> Salut, ton problème c'est que la valeur de retour de surface_rond est
> float, mais le rayon est integer.
[...]

Sorry for the post in French to the list, I thought Didier might like
a reply in French but I didn't mean to post it to the list also.


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

Message: 2
Date: Mon, 02 Nov 2009 02:22:09 -0800
From: Michael Mossey <m...@alumni.caltech.edu>
Subject: Re: [Haskell-beginners] I have created an ugly Haskell
        program..
To: Philip Scott <haskell-beginn...@foo.me.uk>
Cc: beginners@haskell.org
Message-ID: <4aeeb2d1.2080...@alumni.caltech.edu>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed


Function you seek is 'specialZip' below. 'fluff' and 'decapitate' are 
helpers. Not extensively tested.

-- Given a list of ints that "should" all have values, fill in missing
-- values using the "last" value as default.
fluff :: String -> [Int] -> [(Int,String)] -> [(Int,String)]
fluff last (i:is) pss@((t,s):ps)
       | i == t = (i,s) : fluff s is ps
       | i < t  = (i,last) : fluff last is pss
fluff last is [] = zip is (repeat last)


-- Given two lists, remove enough from the front to get to two equal keys.
decapitate [] _ = ([],[])
decapitate _ [] = ([],[])
decapitate xss@((tx,_):xs) yss@((ty,_):ys)
     | tx < ty  = decapitate xs yss
     | ty < tx  = decapitate xss ys
     | ty == tx = (xss,yss)


specialZip d1 d2 =
     let (dd1,dd2) = decapitate d1 d2
         -- build set of every key that should be in final list
         s = S.toAscList . S.fromList $ (map fst dd1) ++ (map fst dd2)
     in case (dd1,dd2) of
          ([],[]) -> []
          (xs1,xs2) ->
              let f1 = fluff "" s xs1 -- use this set to fluff
                  f2 = fluff "" s xs2 -- each list
              -- so final answer can be a simple zipWith
              in zipWith (\(t1,s1) (t2,s2) -> (t1,(s1,s2))) f1 f2

Philip Scott wrote:
> .. and I am positive there must be a way of beautifying it, but I am 
> struggling. I bet there is just some lovely way of making this all shrink to 
> three lines..
> 
> So here's the problem. I have two lists of tuples: (timestamp, value)
> 
> What I would like to do in do a kind of 'zip' on two of these lists to make a 
> list of (timestamp, (value1, value2)) with the following rules:
> 
> - If the timestamps are equal it's easy - make your new element an move on
> - If one of the lists has a timestamp that the other doesn't, repeat an old 
> value from the other list
> - If we don't have an old value yet, then don't create an element in the new 
> list.
> 
> e.g. if I ran my algorithm on these two lists
> 
> d1 = [ (1,"a"), (2,"b"),  (3,"c")           ]
> d2 = [          (2,"b'"),          (4,"d'") ]  
> 
> I would like to get
> 
> result = [ (2, (b,b')), (3, (c,b')), (4, (c,d')) ]  
> 
> e.g. there was no data in d2 for our first element so we skipped it.
> 
> Okay, so here is my code.. It works, but makes me feel a bit dirty. To 
> explain 
> my nomenclature 't' is 'timestamp of', 'v' is 'value of'. vx' and vy' are the 
> 'old' values from the previous iteration in case a repeat is needed. They are 
> Maybes because at the beginning there may be no old value.
> 
> d1 = [ (1,"a"), (2,"b"),  (3,"c")           ]
> d2 = [          (2,"b'"),          (4,"d'") ]  
> 
> t (x,y) = x
> v (x,y) = y
> 
> js vx' vy' (x:xs) (y:ys)
>  | t x == t y  = ( (t x), (v x, v y) )  : js (Just (v x)) (Just (v y)) xs ys
>  | t x < t y   =
>      maybe (js (Just (v x)) Nothing xs (y:ys))
>            (\z -> ( t x, (v x, z ) ) : ( js (Just (v x)) (Just z) xs (y:ys)))
>            vy'
>  | t x > t y   =
>      maybe (js Nothing  (Just (v y)) (x:xs) ys)
>            (\z -> ( t y, (z, v y ) ) : ( js (Just z) (Just (v y)) (x:xs) ys))
>            vx'
> js vx' vy' (x:xs) []   = 
>     maybe []
>           (\z -> ( t x, (v x, z ) ) : ( js (Just (v x)) (Just z) xs []))
>           vy'
> js vx' vy' [] (y:ys)   =
>     maybe []
>           (\z -> ( t y, (z, v y ) ) : ( js (Just z) (Just (v y))  [] ys ))
>           vx'
> js _ _ [] []   = []
> 
> You call it with the first two arguments as Nothing to kick it off (I have a 
> trivial wrapper function to do this)
> 
> It works fine:
> 
>> :t js
> js
>   :: (Ord t) =>
>      Maybe a1 -> Maybe a -> [(t, a1)] -> [(t, a)] -> [(t, (a1, a))]
> 
>> js Nothing Nothing d1 d2
> [(2,("b","b'")),(3,("c","b'")),(4,("c","d'"))]
> 
> But it just feels gross. Any advice on how to tame this beast would be 
> greatly 
> appreciated :)
> 
> All the best, 
> 
> Philip
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners


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

Message: 3
Date: Mon, 02 Nov 2009 11:14:11 +0000
From: Philip Scott <haskell-beginn...@foo.me.uk>
Subject: Re: [Haskell-beginners] I have created an ugly Haskell
        program..
To: Michael Mossey <m...@alumni.caltech.edu>
Cc: beginners@haskell.org
Message-ID: <4aeebf03.5000...@foo.me.uk>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Michael Mossey wrote:
>
> Function you seek is 'specialZip' below. 'fluff' and 'decapitate' are 
> helpers. Not extensively tested.

Thanks Michael, that looks much better than mine :)




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

Message: 4
Date: Mon, 02 Nov 2009 03:43:25 -0800
From: Michael Mossey <m...@alumni.caltech.edu>
Subject: Re: [Haskell-beginners] I have created an ugly Haskell
        program..
To: beginners <beginners@haskell.org>
Message-ID: <4aeec5dd.2010...@alumni.caltech.edu>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Another solution here. The inspiration is to try to use Data.Map's 
fromListWith to do the main work. Notice that you can "decapitate" the 
useless head of each list with the single line

        dropWhile (not . both) . M.toAscList $ neated


import Control.Arrow
import qualified Data.Map as M

data Combine v = LeftOnly v
                | RightOnly v
                | BothOfThem v v
                  deriving (Show)

cmb :: Combine a -> Combine a -> Combine a
cmb (LeftOnly x) (RightOnly y) = BothOfThem x y
cmb (RightOnly y) (LeftOnly x) = BothOfThem x y

both (_,(BothOfThem _ _ )) = True
both _ = False

chain _ last2 ((t,LeftOnly v):xs) = (t,(v,last2)) : chain v last2 xs
chain last1 _ ((t,RightOnly v):xs) = (t,(last1,v)) : chain last1 v xs
chain _ _     ((t,BothOfThem v w):xs) = (t,(v,w)) : chain v w xs
chain _ _     [] = []

specialZip d1 d2 =
     let neated = M.fromListWith cmb $ map (second LeftOnly) d1
                  ++ map (second RightOnly) d2
         dr = dropWhile (not . both) . M.toAscList $ neated
     in chain "" "" dr


Philip Scott wrote:
> Michael Mossey wrote:
>>
>> Function you seek is 'specialZip' below. 'fluff' and 'decapitate' are 
>> helpers. Not extensively tested.
> 
> Thanks Michael, that looks much better than mine :)
> 
> 


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

Message: 5
Date: Mon, 2 Nov 2009 13:15:03 +0100
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Error Handling and case statements
To: beginners@haskell.org
Message-ID: <200911021315.03829.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

Am Montag 02 November 2009 05:57:41 schrieb iæfai:
> I have been trying to work out a problem for the last few hours with  
> little success.
>
> In the following code, using ConfigFile, I obtain the results of the  
> configuration file, but in the main function I am trying to get the  
> Config type out of the case statement. I need to be able to generate  
> that error, but it means the two branches of the case are not the same  
> type.
>
> I am not particularly attached to this direction, I am quite willing  
> to do any way that works. I might be adding more configuration in the  
> future.
>
> Any ideas?
>
> iæfai
> --
> import Network.Shed.Httpd
> import Network.URI
>
> import Data.Either
> import Data.ConfigFile as C
>
> import Control.Monad.Error
> import Control.Applicative
>
> import ChessBoard
>
> data Config = Config { documentRoot :: String } deriving (Read, Show)
>
>
>
> main :: IO ()
> main = do
>      opt <- getConf "./config"
>      config <- case opt of
>          Left (_, err) -> ioError (userError err)
>          Right (config) ->  config
>
>      docPath <- documentRoot config

Wrong type here, documentRoot config :: String

>      putStrLn "Starting up httpd."
>      server <- initServer 6666 request
>      return ()

main = do
    opt <- getConf "./config"
    case opt of
        Left (_,err) -> ioError (userError err)
        Right config -> do
            let docPath = documentRoot config
            putStrLn "Starting up httpd."
            server <- initServer 6666 request
            return ()

-- though if you don't use the server later, it would be better to replace the 
last two 
lines with just "initServer 6666 request"

Perhaps better to separate getting the config from using it:

main = do
    opt <- getConf "./config"
    case opt of
        Left (_,err) -> ioError (userError err)
        Right config -> workWith config

workWith config = do
    let docPath = documentRoot config
    putStrLn ...

>         
> request :: Request -> IO Response
> request req = do
>      putStrLn $ "Recieved " ++ (show $ uriPath $ reqURI req)
>      return $ Response 404 [] "Not found."
>
> -- Mostly from Chris Done's Blog
> getConf :: FilePath -> IO (Either (C.CPErrorData, String) Config)
> getConf filePath = runErrorT $ do
>         let cp = C.emptyCP { optionxform = id }
>         contents <- liftIO $ readFile filePath
>         config <- C.readstring cp contents
>         let get = C.get config "DEFAULT"
>         Config <$> get "Document-Root"



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

Message: 6
Date: Mon, 2 Nov 2009 11:48:09 -0500
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] I have created an ugly Haskell
        program..
To: beginners@haskell.org
Message-ID: <20091102164809.ga11...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Sun, Nov 01, 2009 at 11:27:42PM +0000, Philip Scott wrote:
> .. and I am positive there must be a way of beautifying it, but I am 
> struggling. I bet there is just some lovely way of making this all shrink to 
> three lines..
> 
> So here's the problem. I have two lists of tuples: (timestamp, value)
> 
> What I would like to do in do a kind of 'zip' on two of these lists to make a 
> list of (timestamp, (value1, value2)) with the following rules:
> 
> - If the timestamps are equal it's easy - make your new element an move on
> - If one of the lists has a timestamp that the other doesn't, repeat an old 
> value from the other list
> - If we don't have an old value yet, then don't create an element in the new 
> list.

Ask yourself: What Would Conal Do (WWCD)?  Conal Elliott is always
trying to get people to think about the semantic essence of their
problems, so let's try it.

What are we REALLY trying to do here?  What are those lists of tuples,
REALLY?  Well, it seems to me that the lists of tuples are really just
representing *functions* on some totally ordered domain.  The
list-of-pairs representation takes advantage of the fact that these
functions tend to be constant on whole intervals of the domain; we
only need a tuple to mark the *beginning* of a constant interval.  The
fact that we want to take a value from the last old timestamp when we
don't have a certain timestamp in the list reflects the fact that the
function takes on that value over the whole *interval* from the
timestamp when it occurred to whenever the next timestamp is.

So, let's try converting these lists of pairs to actual functions:


  asFunc :: (Ord a) => [(a,b)] -> (a -> Maybe b)
  asFunc is a = fmap snd . listToMaybe . reverse . takeWhile ((<=a) . fst) $ is


Simple -- we just scan through the list looking for the right
interval.

Now the combining function is just a matter of converting the lists to
functions, and applying those functions to each index we want in the
output list (discarding any Nothings).


  combine :: (Ord a) => [(a,b)] -> [(a,c)] -> [(a,(b,c))]
  combine is js = catMaybes . flip map ixs $ \a ->
                    fmap ((,) a) (liftA2 (,) (asFunc is a) (asFunc js a))
    where ixs = sort . nub $ map fst is ++ map fst js


Done!  

Now, you might object that this is much more inefficient than the
other solutions put forth.  That is very true.  Converting to a
function with 'asFunc' means that we do a linear-time lookup in the
list every time we call the function, so this is O(n^2) overall
instead of O(n).  Building the list of indices ixs in the code above
is also O(n^2) instead of O(n).  However, I still find it very helpful
to think about the essence of the problem like this: elegant yet
inefficient code is a much better starting place than the other way
around!  From here there are several possibilities: maybe this version
is efficient enough, if you'll only be working with small lists.  Or
you can also try to optimize, taking advantage of the fact that we
always call the functions built by asFunc with a sequence of strictly
increasing inputs.  I might make a sort of "iterator" object which
acts like a function (a -> Maybe b), but keeps some extra state so
that as long as you call it with strictly increasing values of a, you
get back a Maybe b (and a new iterator) in constant time.  Of course,
this is really what the other solutions are doing: but thinking about
it this way has helped to structure the solution in a (hopefully) more
clear and elegant way.

-Brent



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

Message: 7
Date: Mon, 2 Nov 2009 14:34:05 -0500
From: aditya siram <aditya.si...@gmail.com>
Subject: [Haskell-beginners] Finding documentation when Hackage is
        down.
To: beginners <beginners@haskell.org>
Message-ID:
        <594f78210911021134y72e7bd11t17cf3d4202530...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hi all,
I use Hackage (through Hayoo sometimes) primarily for viewing API
documentation. How can I  store API docs for cabal-installed packages
locally so I am not slowed down when Hackage goes down?

-deech
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20091102/a75726d8/attachment-0001.html

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

Message: 8
Date: Mon, 2 Nov 2009 20:46:23 +0100
From: Michael Lesniak <mlesn...@uni-kassel.de>
Subject: Re: [Haskell-beginners] Finding documentation when Hackage is
        down.
To: aditya siram <aditya.si...@gmail.com>
Cc: beginners <beginners@haskell.org>
Message-ID:
        <5f8b37690911021146u74c3aedave6a55f5791470...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Hello,

I find http://holumbus.fh-wedel.de/hayoo/hayoo.html very helpful :-)

- Michael


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

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


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

Reply via email to