module Language.Paraiso.Annotation
    (
     Annotation, add, empty, map, set, weakSet, toList, toMaybe
    ) where
import           Control.Monad
import           Data.Dynamic
import           Data.Maybe
import           Prelude hiding (map)
import qualified Prelude as P (map)
type Annotation = [Dynamic]
empty :: Annotation
empty = []
add :: (Typeable a) => a -> Annotation -> Annotation
add x ys = toDyn x : ys
set :: (Typeable a) => a -> Annotation -> Annotation
set x ys = toDyn x : filter ((/= typeOf x) . dynTypeRep) ys
weakSet :: (Typeable a) => a -> Annotation -> Annotation
weakSet x ys 
  | any ((== typeOf x) . dynTypeRep) ys = ys
  | otherwise                           = toDyn x : ys
toList :: (Typeable a) => Annotation -> [a]
toList =  catMaybes . P.map fromDynamic
toMaybe :: (Typeable a) => Annotation -> Maybe a
toMaybe = msum . P.map fromDynamic
map :: (Typeable a, Typeable b) => (a->b) -> Annotation -> Annotation
map f = P.map (maybeApply f)
maybeApply :: (Typeable a, Typeable b) => (a->b) -> Dynamic -> Dynamic
maybeApply f x =
    case dynApply (toDyn f) x of
      Just y  -> y
      Nothing -> x