{-# LANGUAGE Safe #-}
module Text.Show.Value ( Name, Value(..), hideCon ) where
import Data.Maybe(fromMaybe,isNothing)
type Name = String
data Value = Con Name [Value]
| InfixCons Value [(Name,Value)]
| Rec Name [ (Name,Value) ]
| Tuple [Value]
| List [Value]
| Neg Value
| Ratio Value Value
| Integer String
| Float String
| Char String
| String String
| Date String
| Time String
| Quote String
deriving (Eq,Show)
hideCon :: Bool -> (Name -> Bool) -> Value -> Value
hideCon collapse hidden = toVal . delMaybe
where
hiddenV = Con "_" []
toVal = fromMaybe hiddenV
delMany vals
| collapse && all isNothing newVals = Nothing
| otherwise = Just (map toVal newVals)
where
newVals = map delMaybe vals
delMaybe val =
case val of
Con x vs
| hidden x -> Nothing
| null vs -> Just val
| otherwise -> Con x `fmap` delMany vs
Rec x fs
| hidden x -> Nothing
| null fs -> Just val
| collapse && all isNothing mbs -> Nothing
| otherwise -> Just (Rec x [ (f,v) | (f,Just v) <- zip ls mbs ])
where (ls,vs) = unzip fs
mbs = map delMaybe vs
InfixCons v ys
| any hidden cs -> Nothing
| otherwise -> do ~(v1:vs1) <- delMany (v:vs)
Just (InfixCons v1 (zip cs vs1))
where (cs,vs) = unzip ys
Tuple vs | null vs -> Just val
| otherwise -> Tuple `fmap` delMany vs
List vs | null vs -> Just val
| otherwise -> List `fmap` delMany vs
Neg v -> Neg `fmap` delMaybe v
Ratio v1 v2 -> do ~[a,b] <- delMany [v1,v2]
Just (Ratio a b)
Integer {} -> Just val
Float {} -> Just val
Char {} -> Just val
String {} -> Just val
Date {} -> Just val
Time {} -> Just val
Quote {} -> Just val