{-|
Module      : LensUtils
Description : Lens utility functions
Copyright   : (c) Eric Mertens, 2016
License     : ISC
Maintainer  : emertens@gmail.com

This module provides functions that are useful with lenses.

-}
module LensUtils
  (
  -- * Strict update operations
    overStrict
  , setStrict

  -- * time lenses
  , zonedTimeLocalTime
  , localTimeTimeOfDay
  , localTimeDay
  ) where

import Control.Lens (Lens', (??), set, ASetter, LensLike)
import Data.Time (ZonedTime(ZonedTime), LocalTime(LocalTime), Day, TimeOfDay)
import StrictUnit (StrictUnit(..))

-- | Modify the target of a 'Setter' with a function. The result
-- is strict in the results of applying the function. Strict version
-- of 'over'
overStrict :: LensLike ((,) StrictUnit) s t a b -> (a -> b) -> s -> t
overStrict :: forall s t a b.
LensLike ((,) StrictUnit) s t a b -> (a -> b) -> s -> t
overStrict LensLike ((,) StrictUnit) s t a b
l a -> b
f = forall {b}. (StrictUnit, b) -> b
run forall b c a. (b -> c) -> (a -> b) -> a -> c
. LensLike ((,) StrictUnit) s t a b
l (forall {b}. b -> (StrictUnit, b)
nur forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
f)
  where
    nur :: b -> (StrictUnit, b)
nur b
y = (b
y seq :: forall a b. a -> b -> b
`seq` StrictUnit
StrictUnit, b
y)
    run :: (StrictUnit, b) -> b
run (StrictUnit
StrictUnit,b
y) = b
y
{-# INLINE overStrict #-}

-- | Set a value strictly in the set value. Strict version of 'set'.
setStrict :: ASetter s t a b -> b -> s -> t
setStrict :: forall s t a b. ASetter s t a b -> b -> s -> t
setStrict ASetter s t a b
l b
x = forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter s t a b
l forall a b. (a -> b) -> a -> b
$! b
x
{-# INLINE setStrict #-}

-- | 'Lens' to the 'LocalTime' component of a 'ZonedTime'
zonedTimeLocalTime :: Lens' ZonedTime LocalTime
zonedTimeLocalTime :: Lens' ZonedTime LocalTime
zonedTimeLocalTime LocalTime -> f LocalTime
f (ZonedTime LocalTime
t TimeZone
z) = (LocalTime -> TimeZone -> ZonedTime
ZonedTime forall (f :: * -> *) a b. Functor f => f (a -> b) -> a -> f b
?? TimeZone
z) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LocalTime -> f LocalTime
f LocalTime
t
{-# INLINE zonedTimeLocalTime #-}

-- | 'Lens' to the 'TimeOfDay component of a 'LocalTime'.
localTimeTimeOfDay :: Lens' LocalTime TimeOfDay
localTimeTimeOfDay :: Lens' LocalTime TimeOfDay
localTimeTimeOfDay TimeOfDay -> f TimeOfDay
f (LocalTime Day
d TimeOfDay
t) = Day -> TimeOfDay -> LocalTime
LocalTime Day
d forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TimeOfDay -> f TimeOfDay
f TimeOfDay
t
{-# INLINE localTimeTimeOfDay #-}

-- | 'Lens' to the 'TimeOfDay component of a 'LocalTime'.
localTimeDay :: Lens' LocalTime Day
localTimeDay :: Lens' LocalTime Day
localTimeDay Day -> f Day
f (LocalTime Day
d TimeOfDay
t) = (Day -> TimeOfDay -> LocalTime
LocalTime forall (f :: * -> *) a b. Functor f => f (a -> b) -> a -> f b
?? TimeOfDay
t) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Day -> f Day
f Day
d
{-# INLINE localTimeDay #-}