{-# LANGUAGE TypeOperators, RankNTypes #-}
module CHR.Data.Lens.MicroLens
(
(:->)
, Lens
, (^*)
, (^.)
, getL
, (^=)
, (^$=)
, (=:)
, (=$:)
, modifyAndGet
, (=$^:)
, modL
, getl
, mkLabel
, fstl
, sndl
, fst3l
, snd3l
, trd3l
, isoMb
, isoMbWithDefault
)
where
import qualified Control.Monad.State as MS
import Lens.Micro hiding (Lens, lens)
import qualified Lens.Micro as L
import Lens.Micro.Mtl
import Lens.Micro.TH
import Language.Haskell.TH
import CHR.Utils
type Lens a b = Lens' a b
type a :-> b = Lens' a b
lens :: (a -> b) -> (a -> b -> a) -> (a :-> b)
lens = L.lens
{-# INLINE lens #-}
infixl 9 ^*
(^*) :: (a :-> b) -> (b :-> c) -> (a :-> c)
f1 ^* f2 = f1 . f2
{-# INLINE (^*) #-}
getL :: (f :-> a) -> f -> a
getL = flip (^.)
{-# INLINE getL #-}
infixr 4 ^=
(^=) :: (a :-> b) -> b -> a -> a
(^=) = set
{-# INLINE (^=) #-}
infixr 4 ^$=
(^$=) :: (a :-> b) -> (b -> b) -> a -> a
(^$=) = over
{-# INLINE (^$=) #-}
infixr 4 =$^:
(=$^:), modL, modifyAndGet :: MS.MonadState f m => (f :-> o) -> (o -> (a,o)) -> m a
l =$^: f = do
old <- use l
let (res,new) = f old
l =: new
return res
{-# INLINE (=$^:) #-}
modL = (=$^:)
{-# INLINE modL #-}
modifyAndGet = (=$^:)
{-# INLINE modifyAndGet #-}
getl :: MS.MonadState f m => (f :-> o) -> m o
getl = use
infixr 4 =:
(=:) :: MS.MonadState f m => (f :-> o) -> o -> m ()
(=:) = (.=)
{-# INLINE (=:) #-}
infixr 4 =$:
(=$:) :: MS.MonadState f m => (f :-> o) -> (o -> o) -> m ()
(=$:) = modifying
{-# INLINE (=$:) #-}
mkLabel :: Name -> Q [Dec]
mkLabel = makeLenses
fstl :: Lens (a,b) a
fstl = (_1)
{-# INLINE fstl #-}
sndl :: Lens (a,b) b
sndl = (_2)
{-# INLINE sndl #-}
fst3l :: Lens (a,b,c) a
fst3l = (_1)
{-# INLINE fst3l #-}
snd3l :: Lens (a,b,c) b
snd3l = (_2)
{-# INLINE snd3l #-}
trd3l :: Lens (a,b,c) c
trd3l = (_3)
{-# INLINE trd3l #-}
isoMbWithDefault :: o -> (f :-> Maybe o) -> (f :-> o)
isoMbWithDefault dflt f = lens (\a -> maybe dflt id $ a ^. f) (\a b -> set f (Just b) a)
isoMb :: String -> (f :-> Maybe o) -> (f :-> o)
isoMb msg f = lens (\a -> panicJust msg $ a ^. f) (\a b -> set f (Just b) a)