@@ -54,12 +54,6 @@ module Dhall.Core (
5454 -- * Optics
5555 , subExpressions
5656 , chunkExprs
57- , rewriteOf
58- , transformOf
59- , over
60- , rewriteMOf
61- , transformMOf
62- , mapMOf
6357
6458 -- * Miscellaneous
6559 , internalError
@@ -70,9 +64,8 @@ module Dhall.Core (
7064 ) where
7165
7266#if MIN_VERSION_base(4,8,0)
73- import Control.Applicative (WrappedMonad (.. ))
7467#else
75- import Control.Applicative (Applicative (.. ), WrappedMonad ( .. ), (<$>) )
68+ import Control.Applicative (Applicative (.. ), (<$>) )
7669#endif
7770import Control.Applicative (empty )
7871import Control.Exception (Exception )
@@ -84,7 +77,6 @@ import Data.Foldable
8477import Data.Functor.Identity (Identity (.. ))
8578import Data.HashSet (HashSet )
8679import Data.List.NonEmpty (NonEmpty (.. ))
87- import Data.Profunctor.Unsafe ((#.) )
8880import Data.String (IsString (.. ))
8981import Data.Semigroup (Semigroup (.. ))
9082import Data.Sequence (Seq , ViewL (.. ), ViewR (.. ))
@@ -96,7 +88,6 @@ import Dhall.Set (Set)
9688import Dhall.Src (Src )
9789import {- # SOURCE #-} Dhall.Pretty.Internal
9890import GHC.Generics (Generic )
99- import Lens.Family (ASetter , LensLike , over )
10091import Numeric.Natural (Natural )
10192import Prelude hiding (succ )
10293
@@ -2154,49 +2145,3 @@ prettyURIComponent text
21542145throws :: (Exception e , MonadIO io ) => Either e a -> io a
21552146throws (Left e) = liftIO (Control.Exception. throwIO e)
21562147throws (Right r) = return r
2157-
2158- {-| Convenience utility identical to @"Control.Lens".`Control.Lens.rewriteOf`@
2159- re-exported for convenience in order to minimize dependencies on @lens@
2160- -}
2161- rewriteOf :: ASetter a b a b -> (b -> Maybe a ) -> a -> b
2162- rewriteOf l f = go
2163- where
2164- go = transformOf l (\ x -> maybe x go (f x))
2165- {-# INLINE rewriteOf #-}
2166-
2167- {-| Convenience utility identical to @"Control.Lens".`Control.Lens.transformOf`@
2168- re-exported for convenience in order to minimize dependencies on @lens@
2169- -}
2170- transformOf :: ASetter a b a b -> (b -> b ) -> a -> b
2171- transformOf l f = go
2172- where
2173- go = f . over l go
2174- {-# INLINE transformOf #-}
2175-
2176- {-| Convenience utility identical to @"Control.Lens".`Control.Lens.rewriteMOf`@
2177- re-exported for convenience in order to minimize dependencies on @lens@
2178- -}
2179- rewriteMOf
2180- :: Monad m
2181- => LensLike (WrappedMonad m ) a b a b -> (b -> m (Maybe a )) -> a -> m b
2182- rewriteMOf l f = go
2183- where
2184- go = transformMOf l (\ x -> f x >>= maybe (return x) go)
2185- {-# INLINE rewriteMOf #-}
2186-
2187- {-| Convenience utility identical to @"Control.Lens".`Control.Lens.transformMOf`@
2188- re-exported for convenience in order to minimize dependencies on @lens@
2189- -}
2190- transformMOf
2191- :: Monad m => LensLike (WrappedMonad m ) a b a b -> (b -> m b ) -> a -> m b
2192- transformMOf l f = go
2193- where
2194- go t = mapMOf l go t >>= f
2195- {-# INLINE transformMOf #-}
2196-
2197- {-| Convenience utility identical to @"Control.Lens".`Control.Lens.mapMOf`@
2198- re-exported for convenience in order to minimize dependencies on @lens@
2199- -}
2200- mapMOf :: LensLike (WrappedMonad m ) s t a b -> (a -> m b ) -> s -> m t
2201- mapMOf l cmd = unwrapMonad #. l (WrapMonad #. cmd)
2202- {-# INLINE mapMOf #-}
0 commit comments