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 a proper way to make a Set typeclass? and why is it
      not done already? (Markus L?ll)
   2. Re:  Re: problem with System.Directory.Tree (Anand Mitra)
   3. Re:  Re: problem with System.Directory.Tree (Daniel Fischer)
   4. Re:  Re: problem with System.Directory.Tree (Stephen Tetley)
   5. Re:  upgrade Hackage show to QuickCheck 2 for     lambdabot
      (Jonas Almstr?m Dureg?rd)
   6. Fwd: [Haskell-beginners] More Deserialization Woes (Tom Hobbs)


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

Message: 1
Date: Tue, 6 Jul 2010 01:35:41 +0300
From: Markus L?ll <markus.l...@gmail.com>
Subject: [Haskell-beginners] what's a proper way to make a Set
        typeclass? and  why is it not done already?
To: beginners@haskell.org
Message-ID:
        <aanlktinqi97utl36rwvvsrmai5f1s5apl427o5sin...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

I started like this:

{-# LANGUAGE
   MultiParamTypeClasses,
   FlexibleInstances #-}

import qualified Data.List as L

class (Eq e) => Set s e where
   empty :: s e
   fromList :: [e] -> s e
   ...

..and started to implement it on a list:

instance (Eq e) => Set [] e where
   empty = []
   fromList xs = L.nub xs

But I can't understand, why there has to be a (Eq a) context to the
Set instance of a list, when the class definition seems to already say
it? It won't compile without it..

Secondly, why do I need FlexibleInstances -- it gives me an eror which
I don't understand ("all instance types must be of the form T a1 ...
an" and so on, and recommends to add the flexible instances.)

Also I couldn't find other elaborate Set typeclasses -- there seems to
be only the "Set a" type. Why is that(?), because you could use other
datastructures, better and worse in various ways, than the balanced
binary tree..


Markus


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

Message: 2
Date: Tue, 6 Jul 2010 07:31:58 +0530
From: Anand Mitra <mi...@kqinfotech.com>
Subject: Re: [Haskell-beginners] Re: problem with
        System.Directory.Tree
To: beginners@haskell.org
Message-ID:
        <aanlktilbfob4jyluvqvnqtw3g3qanxe8pvqtxgs5r...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

All the advice and help I got on my difficulties till now have been
very useful. My current problem is a little weird and can't
figure out what is happening.

I have been able to get the serialization working with DirTree based
on the suggestions I have received till now. I have a function calcMD5
which given a FilePath will traverse the entire tree calculating the
checksum of each file it encounters. The resultant structure is
serializable by encode. But when I do a encodeFile to store the result
to a file I get nothing.

,----
| *Main> calcMD5 "/tmp/tmp"
| AncTree "/tmp" (DirW {name = "tmp", contents = [FileW {name = "passwd",
file = Prop {md5sum = f54e7cef69973cecdce3c923da2f9222, modTime = Tue Jul  6
07:18:16 IST 2010, filenam = "/tmp/tmp/passwd"}}]})
|
| *Main> liftM encode $ calcMD5 "/tmp/tmp"
| Chunk
"\NUL\NUL\NUL\NUL\NUL\NUL\NUL\EOT/tmp\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\ETXtmp\NUL\NUL\NUL\NUL\NUL\NUL\NUL\SOH\SOH\NUL\NUL\NUL\NUL\NUL\NUL\NUL\ACKpasswd\NUL\245N|\239i\151<\236\220\227\201#\218/\146\"\NULL2\139`\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\SI/tmp/tmp/passwd"
Empty
`----

clearly the encoding is working.
But if I try to use encodeFile to write it to a file the file is not
created.

,----
| *Main> liftM (encodeFile "/tmp/tmp-list") $ calcMD5 "/tmp/tmp"
|
| $ ls /tmp/tmp-list
| ls: cannot access /tmp/tmp-list: No such file or directory
`----

I tried a few other things like converting the Bytestring from encode
into a string using show and then doing a writeFile on
it. Unfortunately none of them worked.

regards
-- 
Anand Mitra

On Mon, Jun 28, 2010 at 1:23 PM, Stephen Tetley <stephen.tet...@gmail.com>wrote:

> Hi Anand
>
> MD5Digest is an abstract type (the constructor is not exported from
> its module) but it is an instance of Binary.
> ClockTime (from System.Time) is not an instance of Binary but it does
> export its constructor.
> Neither are instances of Data.Data.
>
> So I would hand-craft an instance of Binary for the Props datatype
> rather than try to first make them instances of Data.
>
> The code will be something like this, as I don't have MD5 installed it
> is unchecked:
>
> class Binary Props where
>  put (Prop md5 tim name) =
>      do { putWord8 0     -- number each constructor
>         ; put md5        -- MD5Digest has a Binary instance
>         ; putTOD tim
>         ; put name
>         }
>
>  put Blank               =
>      do { putWord8 1 }   -- number each constructor
>
>  get = do { typ <- getWord8 -- get the constructor tag...
>           ; case typ of
>              0 -> getProp
>              1 -> return Blank
>           }
>
> getProp :: Get Props
> getProp = do
>    { md5 <- get
>    ; tim <- getTOD
>    ; name <- get
>    ; return (Prop md5 tim name)
>    }
>
>
> -- ClockTime doesn't have a binary instance
> -- but a it has a single constructor
> --
> -- > TOD Integer Integer -
> --
> -- and Integer has a Binary instance, so I
> -- would make auxillaris for put and get:
>
> putTOD :: ClockTime -> Put ()
> putTOD (TOD a b) = do { put a ; put b }
>
> getTOD :: Get ClockTime
> getTOD = do { a <- get; b <- get; return (TOD a b) }
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20100705/e367d8d1/attachment-0001.html

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

Message: 3
Date: Tue, 6 Jul 2010 09:53:48 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Re: problem with
        System.Directory.Tree
To: beginners@haskell.org
Message-ID: <201007060953.49162.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="utf-8"

On Tuesday 06 July 2010 04:01:58, Anand Mitra wrote:
> All the advice and help I got on my difficulties till now have been
> very useful. My current problem is a little weird and can't
> figure out what is happening.
>
> I have been able to get the serialization working with DirTree based
> on the suggestions I have received till now. I have a function calcMD5
> which given a FilePath will traverse the entire tree calculating the
> checksum of each file it encounters. The resultant structure is
> serializable by encode. But when I do a encodeFile to store the result
> to a file I get nothing.
>
> ,----
>
> | *Main> calcMD5 "/tmp/tmp"
> | AncTree "/tmp" (DirW {name = "tmp", contents = [FileW {name =
> | "passwd",
>
> file = Prop {md5sum = f54e7cef69973cecdce3c923da2f9222, modTime = Tue
> Jul  6 07:18:16 IST 2010, filenam = "/tmp/tmp/passwd"}}]})
>
> | *Main> liftM encode $ calcMD5 "/tmp/tmp"
> | Chunk
>
> "\NUL\NUL\NUL\NUL\NUL\NUL\NUL\EOT/tmp\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\ET
>Xtmp\NUL\NUL\NUL\NUL\NUL\NUL\NUL\SOH\SOH\NUL\NUL\NUL\NUL\NUL\NUL\NUL\ACKp
>asswd\NUL\245N|\239i\151<\236\220\227\201#\218/\146\"\NULL2\139`\NUL\NUL\
>NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\NUL\SI/tmp/tmp/passwd" Empty
> `----
>
> clearly the encoding is working.
> But if I try to use encodeFile to write it to a file the file is not
> created.
>
> ,----
>
> | *Main> liftM (encodeFile "/tmp/tmp-list") $ calcMD5 "/tmp/tmp"

calcMD5 :: IO something

I suppose?

then

liftM (encodeFile "/tmp/tmp-list") $ calcMD5 "/tmp/tmp"

has type

IO (IO ())

and executing that only evaluates the action 
(encodeFile "/tmp/tmp-list" calcMD5Result)
, it doesn't execute it.

What you want is

calcMD5 "/tmp/tmp" >>= encodeFile "/tmp/tmp-list"

> |
> | $ ls /tmp/tmp-list
> | ls: cannot access /tmp/tmp-list: No such file or directory
>
> `----
>
> I tried a few other things like converting the Bytestring from encode
> into a string using show and then doing a writeFile on
> it. Unfortunately none of them worked.
>
> regards



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

Message: 4
Date: Tue, 6 Jul 2010 08:54:19 +0100
From: Stephen Tetley <stephen.tet...@gmail.com>
Subject: Re: [Haskell-beginners] Re: problem with
        System.Directory.Tree
To: Anand Mitra <mi...@kqinfotech.com>
Cc: beginners@haskell.org
Message-ID:
        <aanlktinghkaqcbex-reubks8v5qnh5_gttip9a0fg...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

On 6 July 2010 03:01, Anand Mitra <mi...@kqinfotech.com> wrote:

> | *Main> liftM encode $ calcMD5 "/tmp/tmp"

Try

calcMD5 "/tmp/tmp" >>= encodeFile "/tmp/tmp-list"


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

Message: 5
Date: Tue, 6 Jul 2010 10:39:00 +0200
From: Jonas Almstr?m Dureg?rd <jonas.dureg...@gmail.com>
Subject: Re: [Haskell-beginners] upgrade Hackage show to QuickCheck 2
        for     lambdabot
To: Antoine Latter <aslat...@gmail.com>
Cc: beginners@haskell.org, haskell mailing list
        <haskell-c...@haskell.org>
Message-ID:
        <aanlktimq-0z7ucykstcafjd8g5a8ruqxr3edprwom...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

For some reason the generate function is not in QC2.

Here's a quick fix:

\begin{code}
import Test.QuickCheck.Gen
import System.Random

generate :: Int -> StdGen -> Gen a -> a
generate n rnd (MkGen m) = m rnd' size
  where
   (size, rnd') = randomR (0, n) rnd
\end{code}

Perhaps it would be better to ask the QC maintainers to re-include
this function in the library...

/Jonas

On 3 July 2010 01:09, Antoine Latter <aslat...@gmail.com> wrote:
> Including the café.
>
> On Jul 2, 2010 8:49 AM, "Mark Wright" <markwri...@internode.on.net> wrote:
>
> Hi,
>
> I'm trying to upgrade Hackage show to QuickCheck 2, after
> applying the diffs below (which may not be correct, since I am
> a beginner), I am left which this error message:
>
> runghc ./Setup.hs build
> Preprocessing library show-0.3.4...
> Building show-0.3.4...
> [4 of 4] Compiling ShowQ            ( ShowQ.hs, dist/build/ShowQ.o )
>
> ShowQ.hs:104:20: Not in scope: `generate'
>
> Compilation exited abnormally with code 1 at Fri Jul  2 23:07:17
>
> The error occurs in this method:
>
> tests :: Gen Result -> StdGen -> Int -> Int -> [[String]] -> IO String
> tests gen rnd0 ntest nfail stamps
>  | ntest == 500  = done "OK, passed" ntest stamps
>  | nfail == 1000 = done "Arguments exhausted after" ntest stamps
>  | otherwise = case ok result of
>       Nothing    -> tests gen rnd1 ntest (nfail+1) stamps
>       Just True  -> tests gen rnd1 (ntest+1) nfail (stamp result:stamps)
>       Just False -> return $ "Falsifiable, after "
>                               ++ show ntest
>                               ++ " tests:\n"
>                               ++ reason result
>   where
>      result      = generate (((+ 3) . (`div` 2)) ntest) rnd2 gen
>      (rnd1,rnd2) = split rnd0
>
> The QuickCheck 1 generate method is near the bottom this page:
>
> http://hackage.haskell.org/packages/archive/QuickCheck/1.2.0.0/doc/html/Test-QuickCheck.html
>
> but I can not find generate in QuickCheck 2.  I am wondering if
> you have any ideas on how to fix it?
>
> I'm trying to package lambdabot on Solaris.  I have already packaged
> the Haskell Platform and about 90 packages, they are in:
>
> http://pkgbuild.sourceforge.net/spec-files-extra/
>
> Thanks very much, Mark
>
> here are the diffs:
>
> goanna% diff -wc show-0.3.4-orig/ShowQ.hs show-0.3.4/ShowQ.hs
> *** show-0.3.4-orig/ShowQ.hs    Wed Jan 20 11:24:11 2010
> --- show-0.3.4/ShowQ.hs Fri Jul  2 23:07:13 2010
> ***************
> *** 12,22 ****
> --- 12,25 ----
>
>  import qualified Test.SmallCheck (smallCheck, Testable)
>  import Test.QuickCheck
> + import Test.QuickCheck.Arbitrary
>  import Data.Char
>  import Data.List
>  import Data.Word
>  import Data.Int
>  import System.Random
> + import Control.Exception (evaluate)
> + import Test.QuickCheck.Property (ok, stamp)
>
>  type T = [Int]
>  type I = Int
> ***************
> *** 23,36 ****
> --- 26,45 ----
>
>  instance Arbitrary Char where
>      arbitrary     = choose (minBound, maxBound)
> +
> + instance CoArbitrary Char where
>      coarbitrary c = variant (ord c `rem` 4)
>
>  instance Arbitrary Word8 where
>      arbitrary = choose (minBound, maxBound)
> +
> + instance CoArbitrary Word8 where
>      coarbitrary c = variant (fromIntegral ((fromIntegral c) `rem` 4))
>
>  instance Arbitrary Ordering where
>      arbitrary     = elements [LT,EQ,GT]
> +
> + instance CoArbitrary Ordering where
>      coarbitrary LT = variant 1
>      coarbitrary EQ = variant 2
>      coarbitrary GT = variant 0
> ***************
> *** 37,42 ****
> --- 46,53 ----
>
>  instance Arbitrary Int64 where
>    arbitrary     = sized $ \n -> choose (-fromIntegral n,fromIntegral n)
> +
> + instance CoArbitrary Int64 where
>    coarbitrary n = variant (fromIntegral (if n >= 0 then 2*n else 2*(-n) +
> 1))
>
>  instance (Integral a, Arbitrary a) => Arbitrary (Ratio a) where
> ***************
> *** 48,53 ****
> --- 59,65 ----
>                              else (b % a)
>                           else (a % b)
>
> + instance (Integral a, CoArbitrary a) => CoArbitrary (Ratio a) where
>    coarbitrary m = variant (fromIntegral $ if n >= 0 then 2*n else 2*(-n) +
> 1)
>      where n = numerator m
>
> ***************
> *** 87,93 ****
>         Just False -> return $ "Falsifiable, after "
>                                 ++ show ntest
>                                 ++ " tests:\n"
> !                                ++ unlines (arguments result)
>     where
>        result      = generate (((+ 3) . (`div` 2)) ntest) rnd2 gen
>        (rnd1,rnd2) = split rnd0
> --- 99,105 ----
>         Just False -> return $ "Falsifiable, after "
>                                 ++ show ntest
>                                 ++ " tests:\n"
> !                                ++ reason result
>     where
>        result      = generate (((+ 3) . (`div` 2)) ntest) rnd2 gen
>        (rnd1,rnd2) = split rnd0
> goanna%
>
> _______________________________________________
> 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: 6
Date: Tue, 6 Jul 2010 10:15:12 +0100
From: Tom Hobbs <tvho...@googlemail.com>
Subject: Fwd: [Haskell-beginners] More Deserialization Woes
To: beginners@haskell.org
Message-ID:
        <aanlktiltqdt52tewa9hkhjo8uii6aodhsjfinedix...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Sorry, I meant to send this to the list, rather than just to Stephen (sorry
for the Spam).

Tom


---------- Forwarded message ----------
From: Tom Hobbs <tvho...@googlemail.com>
Date: Tue, Jul 6, 2010 at 10:12 AM
Subject: Re: [Haskell-beginners] More Deserialization Woes
To: Stephen Tetley <stephen.tet...@gmail.com>


Hello again,

I've been reading through various tutorials and they all put IO as the
outermost monad, like you suggest.  However, I don't think that's what I
want.

My IO operation is reading from a network stream, not a file, so I want a
failure halfway through should signify a complete failure.  So, I believe
that the type signature for my function should be;

ping  :: String -> PortNumber -> Maybe (IO [String])

because the result "Just []" is a valid one and does not signify a failure.


However, the result of "IO [Just "a", Just "b", Nothing, Nothing]" would
signify that communication failed halfway through and would not make sense
in my context.  This is what the advice seems to be suggesting I write.  But
in this case, I'd prefer to return "Nothing" to signify that a problem
occurred.

So my first question is; because I want to do something so different from
the majority of the articles I've read; am I in a niche where my requirement
makes sense, or does my requirement make no sense - a theory that is backed
up by the fact that no one else seems to be doing that...

Now, I'm not sure I can get there by myself, since I'm struggling to get the
right incantation of catching errors but I'll keep plugging away at that for
a while.

But can someone help me with my next question also.

Is it possible, to extract the values out of the IO monad so it can be used
in pure functions.

For example, once ping has returned it's Maybe [IO String], I would like to
be able to create another function such as;

purePing :: String -> PortNumber -> Maybe [String]
purePing a p = removeIOMonad (ping a p)
                      where
                      removeIOMonad Nothing = Nothing
                      removeIOMonad []    = Just []
                      removeIOMonad (x:xs)    = clevelDropIOMagic x :
removeIOMonad xs

...or something...

Once the IO [String] has been read from the stream, no further IO is
necessary, so any other function should be able to just use the list and not
worry about the IO stuff.

Again my questions are, Is this an okay thing to do, or is my design/idea
very, very wrong?

Thanks again for the help,

Tom


On Thu, Jul 1, 2010 at 1:53 PM, Stephen Tetley <stephen.tet...@gmail.com>wrote:

> Hi Tom
>
> This is bit that is wrong:
>
> ((UTF.toString name) : readNames (n-1) h)
>
>
> You are trying to cons (:) a String onto an IO [String]:
>
> (UTF.toString name) :: String
>
> (readNames (n-1) h) :: IO [String]
>
> (:) :: a -> [a] -> [a]
>
> This is easy mistake to make, I probably still make it myself now and
> again if I'm typing faster than I'm thinking.
>
> As for ping, you are right that the common answer type will be "IO
> (Maybe [String])" i.e.
>
> ping :: String -> PortNumber -> IO (Maybe [String])
>
>
> Generally you will want IO as the outermost (type-) constructor for an
> expression involving IO, this is because you can't 'escape' IO. There
> are some exceptions where IO isn't the outermost type constructor, the
> common one I can think of is you might want to build a list of IO
> actions [IO ()]. You would then commonly pass on this list to evaluate
> it later with mapM_.
>
>
> Neil Mitchell's "IO without (concentrating) on monads tutorial" is a
> very good place to start:
> http://neilmitchell.blogspot.com/2010/01/haskell-io-without-monads.html
>
> Best wishes
>
> Stephen
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20100706/aaface7e/attachment.html

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

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


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

Reply via email to