I would guess history has a lot to do with it. The whole readP mechanism is pretty old, and many of our modern conventions hadn't really taken hold yet.

On Mon, Jun 8, 2020, 2:54 PM Andreas Abel <andreas.abel@ifi.lmu.de> wrote:
 > readIntP :: Num a => a -> (Char -> Bool) -> (Char -> Int) -> ReadP a

Dunno, but one could guess that people find this function more
convenient to apply, in the spirit of

   readIntP x (('0' <=) .&&. (<= '9')) ((- ord '0') . ord)

One could always add your function, under a different name.

They easily convert into each other, using a function like

   boolToMaybe :: Bool -> a -> Maybe a
   boolToMaybe True  a = Just a
   boolToMaybe False _ = Nothing

On 2020-06-06 01:04, Dannyu NDos wrote:
> Current type signature of readIntP is:
>
> readIntP :: Num a => a -> (Char -> Bool) -> (Char -> Int) -> ReadP a
>
> This seems kinda redundant. It inputs two functions, one checking
> whether a character is valid digit, and the other assigning an integer
> to the digit.
>
> Shouldn't we merge them together to one function? Like this:
>
> importControl.Monad
> importData.Foldable
> importData.Maybe
> importText.ParserCombinators.ReadP
>
> readIntP:: Numa=> a-> (Char-> MaybeInt) -> ReadPa
> readIntP base valDigit = do
> maybeNs <- manyTill (fmap (fmap fromIntegral . valDigit) get) $ do
> str <- fmap (fmap valDigit) look
> casestr of
> []-> return ()
> (Nothing:_) -> return ()
> _ -> pfail
> letn = foldl' (\l r -> casel of
> Nothing -> r
> Just l1 -> fmap (base * l1 +) r
> ) Nothing maybeNs
> guard (isJust n)
> return (fromJust n)
>
>
> _______________________________________________
> Libraries mailing list
> Libraries@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>
_______________________________________________
Libraries mailing list
Libraries@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries