mirror of
https://github.com/github/semantic.git
synced 2024-11-24 08:54:07 +03:00
🔥 the custom ! definition.
This commit is contained in:
parent
584ef4ff66
commit
49009a626b
@ -11,13 +11,13 @@ module SES.Myers
|
||||
, MyersState(..)
|
||||
) where
|
||||
|
||||
import Data.Array ((!))
|
||||
import qualified Data.Array as Array
|
||||
import Data.Ix
|
||||
import Data.Functor.Classes
|
||||
import Data.String
|
||||
import Data.These
|
||||
import GHC.Show hiding (show)
|
||||
import GHC.Stack
|
||||
import Prologue hiding (for, error)
|
||||
import Text.Show (showListWith)
|
||||
|
||||
@ -146,11 +146,6 @@ for all run = foldr (\ a b -> (<|>) <$> run a <*> b) (return Nothing) all
|
||||
{-# INLINE for #-}
|
||||
|
||||
|
||||
-- | Bounds-checked indexing of arrays, preserving the call stack.
|
||||
(!) :: (HasCallStack, Ix i, Show i) => Array.Array i a -> i -> a
|
||||
v ! i = v Array.! i
|
||||
|
||||
|
||||
-- | Lifted showing of arrays.
|
||||
liftShowsVector :: Show i => (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Array.Array i a -> ShowS
|
||||
liftShowsVector sp sl d = liftShowsPrec sp sl d . toList
|
||||
|
Loading…
Reference in New Issue
Block a user