{-# LANGUAGE RankNTypes #-}
module Shpadoinkle.Lens (
generalize
, onSum, onRecord, onRecordEndo
, mapLens, (%>)
, forLens, (<%)
, rounding, defaulting, fracIntegral
) where
import Control.Lens (Iso', Lens', Prism', Traversal', iso,
preview, prism, set, view)
import Data.Maybe (fromMaybe)
import Shpadoinkle.Continuation (Continuous, liftC, liftCMay)
generalize, onRecord :: forall f m s a. Functor m => Continuous f => Lens' s a -> f m a -> f m s
generalize len = liftC (set len) (view len)
onRecord = generalize
{-# INLINE onRecord #-}
{-# INLINE generalize #-}
onRecordEndo :: forall f m s a. Functor m => Continuous f => Lens' s a -> (a -> f m a) -> s -> f m s
onRecordEndo len f s = liftC (set len) (view len) (f $ view len s)
onSum :: forall f m s a. Applicative m => Continuous f => Traversal' s a -> f m a -> f m s
onSum p = liftCMay (set p) (preview p)
{-# INLINE onSum #-}
infixl 8 <%
infixr 8 %>
forLens, (<%) :: forall f m s a. Functor m => Continuous f => s -> Lens' s a -> (a -> f m a) -> f m s
forLens big len f = generalize len . f $ view len big
(<%) = forLens
{-# INLINE forLens #-}
{-# INLINE (<%) #-}
mapLens, (%>) :: forall f m s a. Functor m => Continuous f => (a -> f m a) -> s -> Lens' s a -> f m s
mapLens f big len = forLens big len f
(%>) = mapLens
{-# INLINE mapLens #-}
{-# INLINE (%>) #-}
fracIntegral :: forall s a. Integral a => RealFrac s => Prism' s a
fracIntegral = prism fromIntegral $
\f -> let r = round f in
if fromIntegral r == f then Right r else Left f
rounding :: forall a s. Integral s => RealFrac a => Iso' s a
rounding = iso fromIntegral round
{-# INLINE rounding #-}
defaulting :: a -> Iso' (Maybe a) a
defaulting x = iso (fromMaybe x) Just
{-# INLINE defaulting #-}