module System.Console.CmdArgs.Annotate(
Capture(..), Any(..), fromCapture, defaultMissing,
capture, many, (&=),
capture_, many_, (+=), atom, record, Annotate((:=),(:=+))
) where
import Control.Monad
import Control.Monad.Trans.State
import Data.Data(Data,Typeable)
import Data.List
import Data.Maybe
import Data.IORef
import System.IO.Unsafe
import Control.Exception
import Data.Generics.Any
infixl 2 &=, +=
infix 3 :=
data Capture ann
= Many [Capture ann]
| Ann ann (Capture ann)
| Value Any
| Missing Any
| Ctor Any [Capture ann]
deriving Show
instance Functor Capture where
fmap f (Many xs) = Many $ map (fmap f) xs
fmap f (Ann a x) = Ann (f a) $ fmap f x
fmap f (Value x) = Value x
fmap f (Missing x) = Missing x
fmap f (Ctor x xs) = Ctor x $ map (fmap f) xs
fromCapture :: Capture ann -> Any
fromCapture (Many (x:_)) = fromCapture x
fromCapture (Ann _ x) = fromCapture x
fromCapture (Value x) = x
fromCapture (Missing x) = x
fromCapture (Ctor x _) = x
defaultMissing :: Capture ann -> Capture ann
defaultMissing x = evalState (f Nothing Nothing x) []
where
f ctor field (Many xs) = fmap Many $ mapM (f ctor field) xs
f ctor field (Ann a x) = fmap (Ann a) $ f ctor field x
f ctor field (Value x) = return $ Value x
f (Just ctor) (Just field) (Missing x) = do
s <- get
return $ head $
[x2 | (ctor2,field2,x2) <- s, typeOf ctor == typeOf ctor2, field == field2] ++
err ("missing value encountered, no field for " ++ field ++ " (of type " ++ show x ++ ")")
f _ _ (Missing x) = err $ "missing value encountered, but not as a field (of type " ++ show x ++ ")"
f _ _ (Ctor x xs) | length (fields x) == length xs = do
ys <- zipWithM (g x) (fields x) xs
return $ Ctor (recompose x $ map fromCapture ys) ys
f _ _ (Ctor x xs) = fmap (Ctor x) $ mapM (f Nothing Nothing) xs
g ctor field x = do
y <- f (Just ctor) (Just field) x
modify ((ctor,field,y):)
return y
err x = error $ "System.Console.CmdArgs.Annotate.defaultMissing, " ++ x
ref :: IORef [Either (Capture Any -> Capture Any) (Capture Any)]
ref = unsafePerformIO $ newIORef []
push = modifyIORef ref (Left id :)
pop = do x:xs <- readIORef ref; writeIORef ref xs; return x
change f = modifyIORef ref $ \x -> case x of Left g : rest -> f g : rest ; _ -> error "Internal error in Capture"
add f = change $ \x -> Left $ x . f
set x = change $ \f -> Right $ f x
many :: Data val => [val] -> val
many xs = unsafePerformIO $ do
ys <- mapM (force . Any) xs
set $ Many ys
return $ head xs
addAnn :: (Data val, Data ann) => val -> ann -> val
addAnn x y = unsafePerformIO $ do
add (Ann $ Any y)
evaluate x
return x
capture :: (Data val, Data ann) => val -> Capture ann
capture x = unsafePerformIO $ fmap (fmap fromAny) $ force $ Any x
force :: Any -> IO (Capture Any)
force x@(Any xx) = do
push
res <- try $ evaluate xx
y <- pop
case y of
_ | Left (_ :: RecConError) <- res -> return $ Missing x
Right r -> return r
Left f | not $ isAlgType x -> return $ f $ Value x
| otherwise -> do
cs <- mapM force $ children x
return $ f $ Ctor x cs
(&=) :: (Data val, Data ann) => val -> ann -> val
(&=) x y = addAnn (id_ x) (id_ y)
id_ :: a -> a
id_ x = case unit of () -> x
where unit = reverse "" `seq` ()
data Annotate ann
= forall c f . (Data c, Data f) => (c -> f) := f
| forall c f . (Data c, Data f) => (c -> f) :=+ [Annotate ann]
| AAnn ann (Annotate ann)
| AMany [Annotate ann]
| AAtom Any
| ACtor Any [Annotate ann]
deriving Typeable
(+=) :: Annotate ann -> ann -> Annotate ann
(+=) = flip AAnn
many_ :: [Annotate a] -> Annotate a
many_ = AMany
atom :: Data val => val -> Annotate ann
atom = AAtom . Any
record :: Data a => a -> [Annotate ann] -> Annotate ann
record a b = ACtor (Any a) b
capture_ :: Show a => Annotate a -> Capture a
capture_ (AAnn a x) = Ann a (capture_ x)
capture_ (AMany xs) = Many (map capture_ xs)
capture_ (AAtom x) = Value x
capture_ (_ := c) = Value $ Any c
capture_ (_ :=+ c) = Many $ map capture_ c
capture_ (ACtor x xs)
| not $ null rep = error $ "Some fields got repeated under " ++ show x ++ "." ++ ctor x ++ ": " ++ show rep
| otherwise = Ctor x2 xs2
where
x2 = recompose x $ map fromCapture xs2
xs2 = [fromMaybe (Missing c) $ lookup i is | let is = zip inds $ map capture_ xs, (i,c) <- zip [0..] $ children x]
inds = zipWith fromMaybe [0..] $ map (fieldIndex x) xs
rep = inds \\ nub inds
fieldIndex :: Any -> Annotate a -> Maybe Int
fieldIndex ctor (AAnn a x) = fieldIndex ctor x
fieldIndex ctor (f := _) = fieldIndex ctor (f :=+ [])
fieldIndex ctor (f :=+ _) | isJust res = res
| otherwise = error $ "Couldn't resolve field for " ++ show ctor
where c = recompose ctor [Any $ throwInt i `asTypeOf` x | (i,Any x) <- zip [0..] (children ctor)]
res = catchInt $ f $ fromAny c
fieldIndex _ _ = Nothing
data ExceptionInt = ExceptionInt Int deriving (Show, Typeable)
instance Exception ExceptionInt
throwInt :: Int -> a
throwInt i = throw (ExceptionInt i)
catchInt :: a -> Maybe Int
catchInt x = unsafePerformIO $ do
y <- try (evaluate x)
return $ case y of
Left (ExceptionInt z) -> Just z
_ -> Nothing