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:  Re: Having fun with yesod, and a few         questions came up.
      (Michael Litchard)
   2.  Using the Get monad lazily (MAN)
   3.  Applicative instance for Either String (Michael Mossey)
   4. Re:  Applicative instance for Either String (Michael Mossey)
   5. Re:  Applicative instance for Either String (Stephen Tetley)
   6. Re:  Re: Having fun with yesod,   and a few questions came up.
      (Daniel Fischer)
   7. Re:  Using the Get monad lazily (Daniel Fischer)
   8. Re:  Using the Get monad lazily (MAN)
   9. Re:  Re: Having fun with yesod, and a few         questions came up.
      (aditya siram)


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

Message: 1
Date: Fri, 16 Jul 2010 20:22:36 -0700
From: Michael Litchard <mich...@schmong.org>
Subject: Re: [Haskell-beginners] Re: Having fun with yesod, and a few
        questions came up.
To: Michael Snoyman <mich...@snoyman.com>
Cc: Gour <g...@gour-nitai.com>, beginners@haskell.org
Message-ID:
        <aanlktimcyero3yvaxichgnf3fp4hzhhhlocyo90hx...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

ran into this problem

git fetch http://github.com/snoyberg/yesod-hello.git
fatal: Not a git repository

I did that correctly right?


On Fri, Jul 16, 2010 at 12:02 AM, Michael Snoyman <mich...@snoyman.com> wrote:
> I've put together a repository on github[1] that has examples of hosting a
> simple Yesod application. The nonroot variants show you how to host your
> application at some place other than the domain root.
> I've only included lighttpd config files, since that's all I use on a
> regular basis. I'm happy to take patches from anyone having experience with
> other servers.
>
> Michael
> [1] http://github.com/snoyberg/yesod-hello
> On Thu, Jul 15, 2010 at 11:09 PM, Gour <g...@gour-nitai.com> wrote:
>>
>> On Thu, 15 Jul 2010 11:18:39 -0700
>> >>>>>> "Michael" == Michael Litchard <mich...@schmong.org> wrote:
>>
>> Michael> Yes, thank you. It would be useful for you to package up a
>> Michael> sample application with a lighttpd config file. I would
>> Michael> appreciate that.
>>
>> +1 for cherokee config ;)
>>
>>
>> Sincerely,
>> Gour
>>
>> --
>>
>> Gour  | Hlapicina, Croatia  | GPG key: F96FF5F6
>> ----------------------------------------------------------------
>>
>> _______________________________________________
>> Beginners mailing list
>> Beginners@haskell.org
>> http://www.haskell.org/mailman/listinfo/beginners
>>
>
>


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

Message: 2
Date: Sat, 17 Jul 2010 00:49:47 -0300
From: MAN <elviotoccal...@gmail.com>
Subject: [Haskell-beginners] Using the Get monad lazily
To: beginners@haskell.org
Message-ID: <1279338588.2114.31.ca...@dy-book>
Content-Type: text/plain; charset="UTF-8"

I'm sorry if this matter has already been discussed, but I'm going nuts
here. Attached is the code for a small program, an ubber simplification
of something I'm trying to do which would enormously gain from lazy
serialization. The code, however, is broken... It runs, and does the
job, but it does so strictly.
It's more a self imposed exercise than anything else, but I'd really
like to understand what's going on with this snippet, why it didn't
worked as I thought it would.

The objective is to read a binary file, checking to see if a particular
bit (bit zero) is set or not.
My idea was to use the Get monad to get one Word8 at a time, do the
check, and cons the True/False result of that check with a "results
list".
The reason for this results list lies in that I'll later read through
this results, and it would be great if I could do so lazily, aiming for
the producer-consumer pattern. The 
As you'll see, my code fails to produce the results list lazily. At
first I thought that the list would only escape the Get monad if fully
evaluated. So I added the 'testIn' function, which offers only the head
of that list, running inside the Get monad... but even this triggers the
full traversal of the file.

I've attempted several combinations of "let", trying to induce laziness,
but always to no avail. I am at a loss. Any help is most welcomed.


--- BEGIN CODE ---

import Data.Bits (testBit)
import Data.Word
import System.IO (openBinaryFile, withBinaryFile, IOMode(..))
import Data.Binary.Get
import qualified Data.ByteString.Lazy as B
import Control.Monad (liftM, liftM2)

-- | Check the LSB in a word against the symbol.
check :: Bool -> Word8 -> Bool
{-# INLINE check #-}
check s w = testBit w 0 == s

-- Algorithm to implement:
--   - get a word from lazy buffer.
--   - check whether 'least/most' significant byte is as expected.
--   - cons result in output buffer.
-- The result contains a stream of "checks".

checker :: Bool -> Get Bool
checker s = getWord8 >>= return . check s

go :: Symbol -> Get [Bool]
go s = do
  eof <- isEmpty
  case eof of True  -> return []
              False -> let res = liftM2 (:) (checker s) (go s) in res

--

-- Work inside the Get monad.

-- | return the head of the results... this shouldn't take long!
testIn :: Get Bool
testIn = liftM (head) (go True)

--
--

-- gimmi only the head of the results list
runnerIn :: IO Bool
runnerIn = openBinaryFile testFile ReadMode >>= B.hGetContents >>=
return . runGet testIn

test = openBinaryFile testFile ReadMode >>= B.hGetContents >>= \b -> do
  let rs = runGet (go True) b
  return rs



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

Message: 3
Date: Sat, 17 Jul 2010 02:15:47 -0700
From: Michael Mossey <m...@alumni.caltech.edu>
Subject: [Haskell-beginners] Applicative instance for Either String
To: beginners@haskell.org
Message-ID: <4c4174c3.50...@alumni.caltech.edu>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Why does the following give me an error unless I enable FlexibleInstances?

instance Applicative (Either String) where
   pure x = Right x
   Right g <*> Right x = Right (g x)
   Right _ <*> Left s = Left s
   Left s <*> _ = Left s


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

Message: 4
Date: Sat, 17 Jul 2010 04:14:56 -0700
From: Michael Mossey <m...@alumni.caltech.edu>
Subject: Re: [Haskell-beginners] Applicative instance for Either
        String
To: beginners@haskell.org
Message-ID: <4c4190b0.1060...@alumni.caltech.edu>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Oh I get it. I should use a type variable 's' instead of String.

 > instance Applicative (Either s) where
 >   pure x = Right x
 >   Right g <*> Right x = Right (g x)
 >   Right _ <*> Left s = Left s
 >   Left s <*> _ = Left s

I guess there is already a functor instance of Either s?

Interesting how functors and applicative functors can be thought of as 
containers, but one thing that makes them flexible is that they can contain 
zero, one, or many pieces of data (depending on the functor), and they can 
contain something of a different sort entirely (like Left).

Is it possible to make an applicative functor that contains auxiliary data 
unrelated to the "main" data. I think not, because then there's no way to 
define pure.

Michael Mossey wrote:
> Why does the following give me an error unless I enable FlexibleInstances?
> 
> instance Applicative (Either String) where
>   pure x = Right x
>   Right g <*> Right x = Right (g x)
>   Right _ <*> Left s = Left s
>   Left s <*> _ = Left s
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners


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

Message: 5
Date: Sat, 17 Jul 2010 12:54:42 +0100
From: Stephen Tetley <stephen.tet...@gmail.com>
Subject: Re: [Haskell-beginners] Applicative instance for Either
        String
To: Michael Mossey <m...@alumni.caltech.edu>
Cc: beginners@haskell.org
Message-ID:
        <aanlktindpnopgejo3zuqb9ot41b-bubupedzlbszi...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Const has an Applicative instance that doesn't touch the "subject"
parameter i.e. the rightmost element of the type.

-- Const - drops /b/
newtype Const a b = Const a  deriving (Eq,Show)


instance Functor (Const a) where
  fmap f (Const a) = Const a

The applicative instance obliges the "data" i.e. the first parameter
to be an instance of Monoid:

instance Monoid a => Applicative (Const a) where
  pure b = Const mzero
  Const f <*> Const v = Const (f `mappend` v)


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

Message: 6
Date: Sat, 17 Jul 2010 13:55:25 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Re: Having fun with yesod,     and a few
        questions came up.
To: beginners@haskell.org
Message-ID: <201007171355.28112.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

On Saturday 17 July 2010 05:22:36, Michael Litchard wrote:
> git fetch http://github.com/snoyberg/yesod-hello.git
> fatal: Not a git repository
>
> I did that correctly right?

I'm not familiar with git, but I think it should be

git fetch git://github.com/...



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

Message: 7
Date: Sat, 17 Jul 2010 14:10:33 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Using the Get monad lazily
To: beginners@haskell.org
Message-ID: <201007171410.33553.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="utf-8"

On Saturday 17 July 2010 05:49:47, MAN wrote:
> I'm sorry if this matter has already been discussed, but I'm going nuts
> here. Attached is the code for a small program, an ubber simplification
> of something I'm trying to do which would enormously gain from lazy
> serialization. The code, however, is broken... It runs, and does the
> job, but it does so strictly.

The Get monad has been made strict in binary-0.5.
If you need lazy behaviour, you can try binary-0.4.4 (or earlier), or you 
could write your own lazy Get-wrapper using runGetState (won't be too much 
fun).

HTH,
Daniel


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

Message: 8
Date: Sat, 17 Jul 2010 10:59:36 -0300
From: MAN <elviotoccal...@gmail.com>
Subject: Re: [Haskell-beginners] Using the Get monad lazily
To: Daniel Fischer <daniel.is.fisc...@web.de>
Cc: beginners@haskell.org
Message-ID: <1279375176.2587.1.ca...@dy-book>
Content-Type: text/plain; charset="UTF-8"

That's what I get for not keeping up with the packages. I wish I had
asked sooner (I gotta start checking #haskell)
Thank you, Daniel. 

El sáb, 17-07-2010 a las 14:10 +0200, Daniel Fischer escribió:
> On Saturday 17 July 2010 05:49:47, MAN wrote:
> > I'm sorry if this matter has already been discussed, but I'm going nuts
> > here. Attached is the code for a small program, an ubber simplification
> > of something I'm trying to do which would enormously gain from lazy
> > serialization. The code, however, is broken... It runs, and does the
> > job, but it does so strictly.
> 
> The Get monad has been made strict in binary-0.5.
> If you need lazy behaviour, you can try binary-0.4.4 (or earlier), or you 
> could write your own lazy Get-wrapper using runGetState (won't be too much 
> fun).
> 
> HTH,
> Daniel




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

Message: 9
Date: Sat, 17 Jul 2010 10:18:09 -0400
From: aditya siram <aditya.si...@gmail.com>
Subject: Re: [Haskell-beginners] Re: Having fun with yesod, and a few
        questions came up.
To: Daniel Fischer <daniel.is.fisc...@web.de>
Cc: beginners@haskell.org
Message-ID:
        <aanlktimzip7-sb9bs2ybgoadm-evxekk426kcg355...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

I think you want:
git clone git://....
-deech

On Sat, Jul 17, 2010 at 7:55 AM, Daniel Fischer
<daniel.is.fisc...@web.de> wrote:
> On Saturday 17 July 2010 05:22:36, Michael Litchard wrote:
>> git fetch http://github.com/snoyberg/yesod-hello.git
>> fatal: Not a git repository
>>
>> I did that correctly right?
>
> I'm not familiar with git, but I think it should be
>
> git fetch git://github.com/...
>
> _______________________________________________
> 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


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

Reply via email to