
drtomc:
So the following isn't as clever as the line-noise Don posted, but should be in the ball-park.
Low level loops are irksome, but guaranteed to be quick :P
dropFromEnds p = dropWhile p . dropWhileEnd p
dropWhileEnd p bs = take (findFromEndUntil (not p) bs) bs
takeWhileEnd p bs = drop (findFromEndUntil p bs) bs
{- findFromEndUntil is in ByteString.hs, but is not exported -}
Yep, looks reasonable. With a bit of inlining (check the core) and you'll get the same code anyway. Always good to roll a QuickCheck or two for this kind of stuff, since off-by-one errors are rather easy. This should get you into a testable state: import qualified Data.ByteString as S import Test.QuickCheck.Batch import Test.QuickCheck import Text.Show.Functions import System.Random instance Arbitrary Word8 where arbitrary = choose (97, 105) coarbitrary c = variant (fromIntegral ((fromIntegral c) `rem` 4)) instance Random Word8 where randomR = integralRandomR random = randomR (minBound,maxBound) integralRandomR :: (Integral a, RandomGen g) => (a,a) -> g -> (a,g) integralRandomR (a,b) g = case randomR (fromIntegral a :: Integer, fromIntegral b :: Integer) g of (x,g) -> (fromIntegral x, g) -- define a model in [Word8] tidy_model f = reverse . dropWhile f . reverse . dropWhile f -- and check it prop_tidy_ok f xs = tidy_model f xs == (S.unpack . tidy f . S.pack) xs -- Don