{-# LANGUAGE CPP #-} {-# OPTIONS_HADDOCK show-extensions #-} -- | -- Module : Data.Foldable.Ix -- Copyright : (c) OleksandrZhabenko 2020 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- module Data.Foldable.Ix where import Data.Foldable {-| Function to find out the \'index\' (as the reperesentative of the 'Integral' class) of the first element in the 'Foldable' structure (from the left with indices starting from 0), which equals to the first argument. Returns 'Nothing' if there are no such elements. -} findIdx1 :: (Eq a, Foldable t, Integral b) => a -> t a -> Maybe b findIdx1 x js = (\(_,n1,_) -> if n1 == (-1) then Nothing else Just n1) . foldl' f v $ js where v = (x,-1,0) f (t,n,m) y | n >= 0 = (t,n,m + 1) | y == t = (t,m,m + 1) | otherwise = (t,n,m + 1) {-| Function to find out the \'indices\' of the elements in the 'Foldable' structure (from the left with indices starting from 0) that equal to the first argument. Returns empty list if there are no such elements. Uses two passes through the structure. -} findIdxs :: (Eq a, Foldable t) => a -> t a -> [Int] findIdxs x js = (\(_,ys,_) -> ys) . foldr f v $ js where v = (x,[],length js - 1) f y (t,xs,m) | y == t = (t,m:xs,m - 1) | otherwise = (t,xs,m - 1) {-| Function to find out the \'indices\' of the elements in the 'Foldable' structure (from the left with indices starting from 0) that equal to the first argument. Returns empty list if there are no such elements. Uses just one pass through the structure and additional 'reverse' operation on the resulting list with 'foldl''. -} findIdxsL1 :: (Eq a, Foldable t) => a -> t a -> [Int] findIdxsL1 x js = (\(_,ys,_) -> reverse ys) . foldl' f v $ js where v = (x,[],0) f (t,xs,m) y | y == t = (t,m:xs,m + 1) | otherwise = (t,xs,m + 1)