{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE RankNTypes #-}
module Network.Socket.ReadShow where
import Text.Read ((<++))
import qualified Text.Read as P
import qualified Text.Read.Lex as P
import Control.Monad (mzero)
type Pair a b = (a, b)
{-# INLINE eqFst #-}
eqFst :: Eq a => a -> (a, b) -> Bool
eqFst x = \(x',_) -> x' == x
{-# INLINE eqSnd #-}
eqSnd :: Eq b => b -> (a, b) -> Bool
eqSnd y = \(_,y') -> y' == y
lookBetween :: (Eq a, Eq b) => [Pair a b] -> Either a b -> Either a b
lookBetween ps = \case
Left x | (_,y):_ <- filter (eqFst x) ps -> Right y
Right y | (x,_):_ <- filter (eqSnd y) ps -> Left x
z -> z
type Bijection a b = [Pair a b]
namePrefix :: Int -> String -> (Int -> b -> ShowS) -> b -> ShowS
namePrefix i name f x
| null name = f i x
| otherwise = showParen (i > app_prec) $ showString name . showChar ' ' . f (app_prec+1) x
{-# INLINE namePrefix #-}
defShow :: Eq a => String -> (a -> b) -> (Int -> b -> ShowS) -> (Int -> a -> ShowS)
defShow name unwrap shoPrec = \i x -> namePrefix i name shoPrec (unwrap x)
{-# INLINE defShow #-}
expectPrefix :: String -> P.ReadPrec a -> P.ReadPrec a
expectPrefix name pars
| null name = pars
| otherwise = do
P.lift $ P.expect $ P.Ident name
P.step pars
{-# INLINE expectPrefix #-}
defRead :: Eq a => String -> (b -> a) -> P.ReadPrec b -> P.ReadPrec a
defRead name wrap redPrec = expectPrefix name $ wrap <$> redPrec
{-# INLINE defRead #-}
_showInt :: (Show a) => Int -> a -> ShowS
_showInt = showsPrec
{-# INLINE _showInt #-}
_readInt :: (Bounded a, Integral a) => P.ReadPrec a
_readInt = safeInt
{-# INLINE _readInt #-}
showIntInt :: (Show a, Show b) => Int -> (a, b) -> ShowS
showIntInt i (x, y) = _showInt i x . showChar ' ' . _showInt i y
{-# INLINE showIntInt #-}
readIntInt :: (Bounded a, Integral a, Bounded b, Integral b) => P.ReadPrec (a, b)
readIntInt = do
x <- _readInt
y <- _readInt
return (x, y)
{-# INLINE readIntInt #-}
bijectiveShow :: (Eq a) => Bijection a String -> (Int -> a -> ShowS) -> (Int -> a -> ShowS)
bijectiveShow bi def = \i x ->
case lookBetween bi (Left x) of
Right y -> showString y
_ -> def i x
bijectiveRead :: (Eq a) => Bijection a String -> P.ReadPrec a -> P.ReadPrec a
bijectiveRead bi def = P.parens $ bijective <++ def
where
bijective = do
(P.Ident y) <- P.lexP
case lookBetween bi (Right y) of
Left x -> return x
_ -> mzero
app_prec :: Int
app_prec = 10
{-# INLINE app_prec #-}
safeInt :: forall a. (Bounded a, Integral a) => P.ReadPrec a
safeInt = do
i <- signed
if (i >= fromIntegral (minBound :: a) && i <= fromIntegral (maxBound :: a))
then return $ fromIntegral i
else mzero
where
signed :: P.ReadPrec Integer
signed = P.readPrec