module NumericPrelude.Text where {-* Formatting and parsing. -} {-| Show a value using an infix operator. -} {-# INLINE showsInfixPrec #-} showsInfixPrec :: (Show a, Show b) => String -> Int -> Int -> a -> b -> ShowS showsInfixPrec opStr opPrec prec x y = showParen (prec >= opPrec) (showsPrec opPrec x . showString " " . showString opStr . showString " " . showsPrec opPrec y) {-| Parse a string containing an infix operator. -} {-# INLINE readsInfixPrec #-} readsInfixPrec :: (Read a, Read b) => String -> Int -> Int -> (a -> b -> c) -> ReadS c readsInfixPrec opStr opPrec prec cons = readParen (prec >= opPrec) ((\s -> [(const . cons, s)]) .> readsPrec opPrec .> (filter ((opStr==).fst) . lex) .> readsPrec opPrec) {-| Compose two parsers sequentially. -} infixl 9 .> (.>) :: ReadS (b->c) -> ReadS b -> ReadS c (.>) ra rb = concatMap (\(f,rest) -> map (\(b, rest') -> (f b, rest')) (rb rest)) . ra