Re: [Haskell-cafe] Re: split string into n parts

2006-10-24 Thread Stefan Holdermans

Gah! Brain AWOL. I'm surprised no-one picked me up on
that. Why didn't I use:

splitAtMb n [] = Nothing
splitAtMb n l = Just $ splitAt n l


Actually, I've some code lying around doing exactly this (but without  
the padding ;)), written with the coalgebra inlined:


  split n = unfoldr $ \xs -> case xs of
[] -> Nothing
_  -> Just (splitAt n xs)

Cheers,

  Stefan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: split string into n parts

2006-10-24 Thread Jón Fairbairn
I wrote:
> jim burton <[EMAIL PROTECTED]> wrote:
> > Thankyou! It's http://www.rubyquiz.com - They are mostly well suited to
> > haskell, lot of mazes etc. I've done 5 or 6 with varying degrees of success
> > but have learned a lot. This thing about strings in fifths is from #1, the
> > solitaire cipher.
> 
> At a quick glance I can't see which bit needs it. The only
> mention of five is where it asks to split the string into
> groups of five characters (not into five equal parts),
> padded with Xs.
> 
> You can do that like this:
> 
>splitAtMb n l = let p = splitAt n l
>in if null $ fst p
>   then Nothing
>   else Just p

Gah! Brain AWOL. I'm surprised no-one picked me up on
that. Why didn't I use:

splitAtMb n [] = Nothing
splitAtMb n l = Just $ splitAt n l

?

>in_fives l = unfoldr (splitAtMb 5)
> (l ++ replicate (length l `mod` 5) 'X')

And using length makes this over-strict.

maybe something like

groups_of n = unfoldr (splitPad 5)
where splitPad [] = Nothing
  splitPad l = Just $ mapFst (padwith 'X') (splitAt n l)

padwith c l = take n $ l ++ replicate n c
mapFst f (a,b) = (f a, b) -- in Data.Graph.Inductive.Query.Monad

which is a little bit inefficient, but less clunky than
checking for the end of list in order to apply padwith just
once.

-- 
Jón Fairbairn [EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: split string into n parts

2006-10-23 Thread Jón Fairbairn
jim burton <[EMAIL PROTECTED]> writes:

> tweak to in_fives
> 
> > in_fives l = unfoldr (splitAtMb 5)
> >  (l ++ replicate (5 - length l `mod` 5) 'X')

Whoops! Yes.  And a slapped wrist for me for writing a
constant three times. Serves me right for not writing

groups_of n l = unfolder (splitAtMb n) ...
in_fives = groups_of 5

:-)


-- 
Jón Fairbairn [EMAIL PROTECTED]


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: split string into n parts

2006-10-23 Thread Jón Fairbairn
jim burton <[EMAIL PROTECTED]> writes:

> Paul Brown-4 wrote:
> > 
> >> Cool idea!  Can you post a link for the puzzles?
> > 
> Thankyou! It's http://www.rubyquiz.com - They are mostly well suited to
> haskell, lot of mazes etc. I've done 5 or 6 with varying degrees of success
> but have learned a lot. This thing about strings in fifths is from #1, the
> solitaire cipher.

At a quick glance I can't see which bit needs it. The only
mention of five is where it asks to split the string into
groups of five characters (not into five equal parts),
padded with Xs.

You can do that like this:

   splitAtMb n l = let p = splitAt n l
   in if null $ fst p
  then Nothing
  else Just p

   in_fives l = unfoldr (splitAtMb 5)
(l ++ replicate (length l `mod` 5) 'X')

To break a string into five equal parts with the last padded
with Xs, try this:

   fifths l = let len = length l
  part_length = (len+4)`div`5
  pad_length = 5*part_length - len
  in unfoldr (splitAtMb part_length)
 (l ++ replicate pad_length 'X')

I haven't checked these at all carefully, but at least they
illustrate the use of unfoldr.  [aside: One might argue that
the prelude ought to provide splitAtMb rather than splitAt.]

-- 
Jón Fairbairn [EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe