11{-# LANGUAGE Trustworthy #-}
2+ {-# LANGUAGE RankNTypes #-}
23
34{- | Main module that reexports all functionality allowed to use
45without importing any other modules. Just add next lines to your
@@ -80,8 +81,26 @@ module Universum
8081 , module Universum.VarArg
8182
8283 -- * Lenses
83- , module Lens.Micro
84- , module Lens.Micro.Mtl
84+ , Lens
85+ , Lens'
86+ , Traversal
87+ , Traversal'
88+ , over
89+ , set
90+ , (%~)
91+ , (.~)
92+ , (^.)
93+ , (^..)
94+ , (^?)
95+ , _1
96+ , _2
97+ , _3
98+ , _4
99+ , _5
100+ , preuse
101+ , preview
102+ , use
103+ , view
85104 ) where
86105
87106import Universum.Applicative
@@ -104,6 +123,95 @@ import Universum.TypeOps
104123import Universum.VarArg
105124
106125-- Lenses
107- import Lens.Micro (Lens , Lens' , Traversal , Traversal' , over , set , (%~) , (&) , (.~) , (<&>) , (^.) ,
108- (^..) , (^?) , _1 , _2 , _3 , _4 , _5 )
109- import Lens.Micro.Mtl (preuse , preview , use , view )
126+ import qualified Lens.Micro (ASetter , Getting , over , set , (%~) , (.~) , (^.) ,
127+ (^..) , (^?) , _1 , _2 , _3 , _4 , _5 )
128+ import qualified Lens.Micro.Mtl (preuse , preview , use , view )
129+ import Lens.Micro.Internal (Field1 , Field2 , Field3 , Field4 , Field5 )
130+
131+ {-# DEPRECATED
132+ Lens
133+ , Lens'
134+ , Traversal
135+ , Traversal'
136+ , over
137+ , set
138+ , (%~)
139+ , (.~)
140+ , (^.)
141+ , (^..)
142+ , (^?)
143+ , _1
144+ , _2
145+ , _3
146+ , _4
147+ , _5
148+ , preuse
149+ , preview
150+ , use
151+ , view
152+ "Use corresponding function from 'lens' or 'microlens' package"
153+ #-}
154+
155+ type Lens s t a b = forall f . Functor f = > (a -> f b ) -> s -> f t
156+ type Lens' s a = Lens s s a a
157+
158+ type Traversal s t a b = forall f . Applicative f = > (a -> f b ) -> s -> f t
159+ type Traversal' s a = Traversal s s a a
160+
161+ over :: Lens.Micro. ASetter s t a b -> (a -> b ) -> s -> t
162+ over = Lens.Micro. over
163+
164+ set :: Lens.Micro. ASetter s t a b -> b -> s -> t
165+ set = Lens.Micro. set
166+
167+ (%~) :: Lens.Micro. ASetter s t a b -> (a -> b ) -> s -> t
168+ (%~) = (Lens.Micro. %~)
169+
170+ infixr 4 %~
171+
172+ (.~) :: Lens.Micro. ASetter s t a b -> b -> s -> t
173+ (.~) = (Lens.Micro. .~)
174+
175+ infixr 4 .~
176+
177+ (^.) :: s -> Lens.Micro. Getting a s a -> a
178+ (^.) = (Lens.Micro. ^.)
179+
180+ infixl 8 ^.
181+
182+ (^..) :: s -> Lens.Micro. Getting (Endo [a ]) s a -> [a ]
183+ (^..) = (Lens.Micro. ^..)
184+
185+ infixl 8 ^..
186+
187+ (^?) :: s -> Lens.Micro. Getting (First a ) s a -> Maybe a
188+ (^?) = (Lens.Micro. ^?)
189+
190+ infixl 8 ^?
191+
192+ _1 :: Field1 s t a b => Lens s t a b
193+ _1 = Lens.Micro. _1
194+
195+ _2 :: Field2 s t a b => Lens s t a b
196+ _2 = Lens.Micro. _2
197+
198+ _3 :: Field3 s t a b => Lens s t a b
199+ _3 = Lens.Micro. _3
200+
201+ _4 :: Field4 s t a b => Lens s t a b
202+ _4 = Lens.Micro. _4
203+
204+ _5 :: Field5 s t a b => Lens s t a b
205+ _5 = Lens.Micro. _5
206+
207+ preuse :: MonadState s m => Lens.Micro. Getting (First a ) s a -> m (Maybe a )
208+ preuse = Lens.Micro.Mtl. preuse
209+
210+ preview :: MonadReader s m => Lens.Micro. Getting (First a ) s a -> m (Maybe a )
211+ preview = Lens.Micro.Mtl. preview
212+
213+ use :: MonadState s m => Lens.Micro. Getting a s a -> m a
214+ use = Lens.Micro.Mtl. use
215+
216+ view :: MonadReader s m => Lens.Micro. Getting a s a -> m a
217+ view = Lens.Micro.Mtl. view
0 commit comments