never executed always true always false
    1 {-# LANGUAGE UndecidableInstances #-}
    2 module HelVM.HelIO.Containers.LLIndexSafe where
    3 
    4 import           HelVM.HelIO.Control.Safe
    5 
    6 import           Data.ListLike            hiding (show)
    7 
    8 import           Prelude                  hiding (break, divMod, drop, fromList, length, splitAt, swap, uncons)
    9 
   10 -- | Index
   11 naturalIndexSafe :: (MonadSafe m , IndexSafe full item) => full -> Natural -> m item
   12 naturalIndexSafe l =  indexSafe l <$> fromIntegral
   13 
   14 -- | Type Class
   15 class IndexSafe full item | full -> item where
   16   findWithDefault :: item -> Int -> full -> item
   17   findMaybe  :: Int -> full -> Maybe item
   18   indexMaybe :: full -> Int -> Maybe item
   19   findSafe   :: MonadSafe m => Int -> full -> m item
   20   indexSafe  :: MonadSafe m => full -> Int -> m item
   21 
   22 instance ListLike full item => IndexSafe full item where
   23   findWithDefault e i = fromMaybe e <$> findMaybe i
   24   findMaybe           = flip indexMaybe
   25   indexMaybe      l   = rightToMaybe <$> indexSafe l
   26   findSafe            = flip indexSafe
   27   indexSafe           = indexSafeLL
   28 
   29 -- | Internal functions
   30 indexSafeLL :: (MonadSafe m , ListLike full item) => full -> Int -> m item
   31 indexSafeLL l i
   32   | i < 0     = liftErrorWithTupleList "LLIndexSafe.indexSafeLL: index must be >= 0" [("i" , show i)]
   33   | ll <= i   = liftErrorWithTupleList "LLIndexSafe.indexSafeLL: index must not found" [("i" , show i) , ("length l" , show ll)]
   34   | otherwise = (pure <$> index l) i
   35     where ll = length l