{-# LANGUAGE CPP, RankNTypes, Safe #-} {- | This module provides types and functions that require 'Contravariant'; they aren't included in the main microlens package because has a lot of dependencies. -} module Lens.Micro.Contra ( -- * Getter Getter, fromSimpleGetter, -- * Fold Fold, fromSimpleFold, ) where import Lens.Micro import Lens.Micro.Extras (view) import Data.Foldable (traverse_) import Data.Functor.Contravariant (phantom, Contravariant) #if __GLASGOW_HASKELL__ < 710 import Control.Applicative #endif {- | This is the same thing as 'SimpleGetter' but more generalised (so that it would fully match the type used in lens). -} type Getter s a = forall f. (Contravariant f, Functor f) => (a -> f a) -> s -> f s {- | Turn a 'SimpleGetter' into a true 'Getter'. -} fromSimpleGetter :: SimpleGetter s a -> Getter s a fromSimpleGetter g f = phantom . f . view g {-# INLINE fromSimpleGetter #-} {- | This is the same thing as 'SimpleFold' but more generalised (so that it would fully match the type used in lens). See documentation of 'SimpleFold' for the list of functions that work on 'Fold' but don't work on 'SimpleFold'. -} type Fold s a = forall f. (Contravariant f, Applicative f) => (a -> f a) -> s -> f s {- | Turn a 'SimpleFold' into a true 'Fold'. -} fromSimpleFold :: SimpleFold s a -> Fold s a fromSimpleFold g f = phantom . traverse_ f . toListOf g {-# INLINE fromSimpleFold #-}