Send Beginners mailing list submissions to
        [email protected]

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.  lifting to applicative: recomputing an argument  each time it
      is used? (Iain Nicol)
   2. Re:  lifting to applicative: recomputing an argument each
      time it is used? (Chadda? Fouch?)
   3. Re:  lifting to applicative: recomputing an argument each
      time it is used? (Chadda? Fouch?)
   4. Re:  lifting to applicative: recomputing an argument each
      time it is used? (Iain Nicol)
   5.  sometimes Haskell isn't what you want (Dennis Raddle)
   6. Re:  sometimes Haskell isn't what you want (KC)
   7. Re:  lifting to applicative: recomputing an argument each
      time it is used? (Chadda? Fouch?)


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

Message: 1
Date: Sat, 8 Sep 2012 15:49:13 +0100
From: Iain Nicol <[email protected]>
Subject: [Haskell-beginners] lifting to applicative: recomputing an
        argument        each time it is used?
To: [email protected]
Message-ID:
        <CAF4HW_V=wboche7faeufm-awhmery7z9zkrds9pmxagdt9o...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Hi,

I think I'm trying to lift 'Data.List.intersperse' (to applicative or a
monad) in such a way that its (first) argument is recomputed each time
it is used.  I'm hoping that there's a reusable, elegant or abstract,
approach for this that I'm unaware of.

If that isn't clear, I'm using QuickCheck to generate a "sentence" of a
random number of random words, each word separated by a random number of
spaces.  Importantly, there should be no connection between the number
of spaces separating the first and second word, and the number of spaces
separating the second and third word, etc.

I have code which works (run 'workingExample'), but it's not very
elegant---I ended up implementing the 'myIntersperse' function manually.
I had tried to write the code by fmap-ing Data.List.intersperse (see
'badExample'), but doing that na?vely has a major problem.  With that
approach, the number of spaces between each word is correctly random
between sentences, but is incorrectly constant within each generated
sentence.

If anybody knows a trick that I'm missing, that would be great.

Thanks.



{-# LANGUAGE ScopedTypeVariables #-}
import Control.Applicative
import Control.Monad
import Data.List (intersperse)
import Test.QuickCheck

-- | Generate a string consisting of one or more space character.
spaces :: Gen String
spaces = elements [" ", "      "]

-- Generate a (nonsensical) word.
word :: Gen String
word = elements ["foo", "bar", "baz", "bert"]

workingExample, badExample :: IO ()
workingExample = sample $ myIntersperse spaces (listOf word)
badExample = sample $ intersperse <$> spaces <*> listOf word

-- Like a lifted version of 'Data.List.intersperse'.  The interspersed
-- seperator is generated each time the separator appears, as opposed to
-- just once for the whole list.
myIntersperse :: Gen a -> Gen [a] -> Gen [a]
myIntersperse genSep genList = myIntersperse' genSep =<< genList
  where myIntersperse' :: forall a . Gen a -> [a] -> Gen [a]
        myIntersperse' genSep [] = return []
        myIntersperse' genSep xs = do
          let listElementWithSep :: Gen [(a, a)]
              listElementWithSep = zipWithM (\el sep -> pure (el, sep))
                                     xs
                                     =<< (sequence . repeat) genSep
          init <$> tupleListToList <$> listElementWithSep
        -- | Removes the tuple structure from a list, preserving the
        -- inner elements and their order.
        tupleListToList :: [(a, a)] -> [a]
        tupleListToList = concat . map (\(x, y) -> [x, y])


-- 
Iain



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

Message: 2
Date: Sat, 8 Sep 2012 17:40:39 +0200
From: Chadda? Fouch? <[email protected]>
Subject: Re: [Haskell-beginners] lifting to applicative: recomputing
        an argument each time it is used?
To: Iain Nicol <[email protected]>
Cc: [email protected]
Message-ID:
        <canfjzrb61jne-oog7ratagas5flwck5jvkmzwwdpb46zemk...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

On Sat, Sep 8, 2012 at 4:49 PM, Iain Nicol <[email protected]> wrote:

> Hi,
>
> I think I'm trying to lift 'Data.List.intersperse' (to applicative or a
> monad) in such a way that its (first) argument is recomputed each time
> it is used.  I'm hoping that there's a reusable, elegant or abstract,
> approach for this that I'm unaware of.
>

Instead of using intersperse, just generate two list and interlace them
(interlace is easy to write, though not in Data.List :

> interlace (x:xs) (y:ys) = x : y : interlace xs ys
> interlace xs [] = xs
> interlace [] ys = ys
>
> listOfN n g = replicateM n g
>
> mixIntersperse genSep genWord = do
>   n <- arbitrary
>   ws <- listOfN n genWord
>   ss <- listOfN (n-1) genSep
>   return $ interlace ws ss

That seems more elegant to me but you'll judge :)

-- 
Jeda?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120908/5df5f56f/attachment-0001.htm>

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

Message: 3
Date: Sat, 8 Sep 2012 17:46:18 +0200
From: Chadda? Fouch? <[email protected]>
Subject: Re: [Haskell-beginners] lifting to applicative: recomputing
        an argument each time it is used?
To: Iain Nicol <[email protected]>
Cc: [email protected]
Message-ID:
        <CANfjZRabk=Cu=o75zmc2hcomwaphy3gs1zbgmpvfosrevvl...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

On Sat, Sep 8, 2012 at 5:40 PM, Chadda? Fouch? <[email protected]>wrote:

> > listOfN n g = replicateM n g
> >
> > mixIntersperse genSep genWord = do
> >   n <- arbitrary
>

Probably you should rather use

> Positive n <- arbitrary

No reason to waste your time checking empty lists after all...


> >   ws <- listOfN n genWord
> >   ss <- listOfN (n-1) genSep
> >   return $ interlace ws ss
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120908/901545d0/attachment-0001.htm>

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

Message: 4
Date: Sun, 9 Sep 2012 00:29:38 +0100
From: Iain Nicol <[email protected]>
Subject: Re: [Haskell-beginners] lifting to applicative: recomputing
        an argument each time it is used?
To: Chadda? Fouch? <[email protected]>
Cc: [email protected]
Message-ID:
        <caf4hw_u9jn1szrtnmbestxbkydr3a3snz8uajt2_usakjmn...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

On 2012-09-09, Chadda? Fouch? <[email protected]> wrote:
> On Sat, Sep 8, 2012 at 4:49 PM, Iain Nicol <[email protected]> wrote:
>
>> Hi,
>>
>> I think I'm trying to lift 'Data.List.intersperse' (to applicative or
>> a monad) in such a way that its (first) argument is recomputed each
>> time it is used.
>
> Instead of using intersperse, just generate two list and interlace
> them (interlace is easy to write, though not in Data.List [...] That
> seems more elegant to me but you'll judge :)

I appreciate the response.  Your suggestion was indeed significantly
cleaner than what I had come up with.  And your second response has
encouraged me to explore the "Test.QuickCheck.Modifiers" module in
general.

Nonetheless, I was still hoping to reuse the intersperse function, and
so I spent "a little" bit more time on this problem.  After hours of
experimenting in the wrong direction, the following accidentally came to
me:


import Test.QuickCheck (elements, Gen, sized)
import Data.List (intersperse)

mixIntersperse :: Gen String -> Gen String -> Gen [String]
mixIntersperse genSep genWord =
  sized (sequence . intersperse genSep . (`replicate` genWord))


Thanks,
--
Iain



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

Message: 5
Date: Sun, 9 Sep 2012 01:10:14 -0700
From: Dennis Raddle <[email protected]>
Subject: [Haskell-beginners] sometimes Haskell isn't what you want
To: Haskell Beginners <[email protected]>
Message-ID:
        <CAKxLvorVT5hXkGh-738LBU=i-w1nemxvpl3m8jyspqqtz-q...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Sadly, I've decided Haskell is not the right language for my current
project. Python is better. I need to hack together data, and strict typing
is getting in the way. Most of my algorithms are better served with
imperative/mutable-data. I learned a lot about Haskell trying to do it, but
my knowledge of the language is not quiet good enough and I feel like I'm
fighting the language. Python is better. For now.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120909/da5a549b/attachment-0001.htm>

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

Message: 6
Date: Sun, 9 Sep 2012 01:15:47 -0700
From: KC <[email protected]>
Subject: Re: [Haskell-beginners] sometimes Haskell isn't what you want
To: Dennis Raddle <[email protected]>
Cc: Haskell Beginners <[email protected]>
Message-ID:
        <camlkxynh3i2ssqmezzyt-oqpdi19dsjrmupicl_u4mh5_dh...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

If one programming language suited every computable problem there
would only be one programming language.

You don't seem to have a point worth making without more description
of your problem.


On Sun, Sep 9, 2012 at 1:10 AM, Dennis Raddle <[email protected]> wrote:
> Sadly, I've decided Haskell is not the right language for my current
> project. Python is better. I need to hack together data, and strict typing
> is getting in the way. Most of my algorithms are better served with
> imperative/mutable-data. I learned a lot about Haskell trying to do it, but
> my knowledge of the language is not quiet good enough and I feel like I'm
> fighting the language. Python is better. For now.
>
>
> _______________________________________________
> Beginners mailing list
> [email protected]
> http://www.haskell.org/mailman/listinfo/beginners
>



-- 
--
Regards,
KC



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

Message: 7
Date: Sun, 9 Sep 2012 10:44:32 +0200
From: Chadda? Fouch? <[email protected]>
Subject: Re: [Haskell-beginners] lifting to applicative: recomputing
        an argument each time it is used?
To: Iain Nicol <[email protected]>
Cc: [email protected]
Message-ID:
        <CANfjZRbh3K5+LwO1nScP6fqe6erQ=cwjz2ad5fz_c--0kj0...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

On Sun, Sep 9, 2012 at 1:29 AM, Iain Nicol <[email protected]> wrote:

>
> mixIntersperse :: Gen String -> Gen String -> Gen [String]
> mixIntersperse genSep genWord =
>   sized (sequence . intersperse genSep . (`replicate` genWord))
>
>
Very nice :-) (And stupid of me not to think of creating a list of Gen
directly !)

-- 
Jeda?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120909/fd7456ec/attachment-0001.htm>

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

_______________________________________________
Beginners mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 51, Issue 12
*****************************************

Reply via email to