-- |
-- Module: Optics.Operators.Unsafe
-- Description: Definitions of unsafe infix operators for optics.
--
module Optics.Operators.Unsafe
  ( (^?!)
  )
  where

import Data.Maybe (fromMaybe)
import GHC.Stack (HasCallStack)

import Optics.AffineFold
import Optics.Optic
import Optics.Operators

-- | Perform an *UNSAFE* 'head' of an affine fold assuming that it is there.
--
-- >>> Left 4 ^?! _Left
-- 4
--
-- >>> "world" ^?! ix 3
-- 'l'
--
-- >>> [] ^?! _head
-- *** Exception: (^?!): empty affine fold
-- ...
--
-- @since 0.3
(^?!) :: (HasCallStack, Is k An_AffineFold) => s -> Optic' k is s a -> a
s
s ^?! :: s -> Optic' k is s a -> a
^?! Optic' k is s a
o = a -> Maybe a -> a
forall a. a -> Maybe a -> a
fromMaybe ([Char] -> a
forall a. HasCallStack => [Char] -> a
error [Char]
"(^?!): empty affine fold") (s
s s -> Optic' k is s a -> Maybe a
forall k s (is :: IxList) a.
Is k An_AffineFold =>
s -> Optic' k is s a -> Maybe a
^? Optic' k is s a
o)
{-# INLINE (^?!) #-}

infixl 8 ^?!

-- $setup
-- >>> import Optics.Core