{-# LANGUAGE CPP #-}
{-# LANGUAGE Rank2Types #-}
#ifndef MIN_VERSION_base
#define MIN_VERSION_base(x,y,z) 1
#endif
module Data.Typeable.Lens
( _cast
, _gcast
) where
import Control.Lens
import Data.Typeable
import Data.Maybe
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative
#endif
_cast :: (Typeable s, Typeable a) => Traversal' s a
_cast f s = case cast s of
Just a -> fromMaybe (error "_cast: recast failed") . cast <$> f a
Nothing -> pure s
{-# INLINE _cast #-}
_gcast :: (Typeable s, Typeable a) => Traversal' (c s) (c a)
_gcast f s = case gcast s of
Just a -> fromMaybe (error "_gcast: recast failed") . gcast <$> f a
Nothing -> pure s
{-# INLINE _gcast #-}