{-# LANGUAGE CPP #-}
#if MIN_VERSION_base(4,9,0)
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE StandaloneDeriving #-}
#endif
module Reflex.FunctorMaybe
( FunctorMaybe (..)
) where
import Data.IntMap (IntMap)
import Data.Map (Map)
#if MIN_VERSION_base(4,9,0)
import Data.Semigroup (Option(..))
#endif
import Data.Witherable
{-# DEPRECATED FunctorMaybe "Use 'Filterable' from Data.Witherable instead" #-}
class FunctorMaybe f where
fmapMaybe :: (a -> Maybe b) -> f a -> f b
instance FunctorMaybe Maybe where
fmapMaybe = mapMaybe
#if MIN_VERSION_base(4,9,0)
deriving instance FunctorMaybe Option
#endif
instance FunctorMaybe [] where
fmapMaybe = mapMaybe
instance FunctorMaybe (Map k) where
fmapMaybe = mapMaybe
instance FunctorMaybe IntMap where
fmapMaybe = mapMaybe