-----------------------------------------------------------------------------
-- |
-- Module      :  Control.Seq.Lens
-- Copyright   :  (C) 2012-16 Edward Kmett
-- License     :  BSD-style (see the file LICENSE)
-- Maintainer  :  Edward Kmett <ekmett@gmail.com>
-- Stability   :  provisional
-- Portability :  portable
--
-- A t'Fold' can be used to take the role of 'Foldable' in @Control.Seq@.
----------------------------------------------------------------------------
module Control.Seq.Lens
  ( seqOf
  ) where

import Control.Lens
import Control.Seq
import Data.Monoid

-- | Evaluate the elements targeted by a t'Lens', t'Traversal', t'Iso',
-- t'Getter' or t'Fold' according to the given strategy.
--
-- @'seqFoldable' = 'seqOf' 'folded'@
seqOf :: Getting (Endo [a]) s a -> Strategy a -> Strategy s
seqOf :: forall a s. Getting (Endo [a]) s a -> Strategy a -> Strategy s
seqOf Getting (Endo [a]) s a
l Strategy a
s = forall a. Strategy a -> Strategy [a]
seqList Strategy a
s forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a s. Getting (Endo [a]) s a -> s -> [a]
toListOf Getting (Endo [a]) s a
l
{-# INLINE seqOf #-}