module Hedgehog.Extras.Stock.String
  ( strip
  , lastLine
  , firstLine
  , readNoteM
  ) where

import           Control.Monad.Catch (MonadCatch)
import           Data.Bifunctor
import           Data.Function
import           Data.Semigroup
import           Data.String
import           GHC.Stack
import           Text.Read
import           Text.Show (Show)

import qualified Data.List as L
import qualified Data.Text as T
import qualified Hedgehog as H
import qualified Hedgehog.Extras.Test.Base as H

-- | Strip whitespace from the beginning and end of the string.
strip :: String -> String
strip :: String -> String
strip = Text -> String
T.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.strip forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack

-- | Get the last line in the string
lastLine :: String -> String
lastLine :: String -> String
lastLine = String -> String
strip forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
L.unlines forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
L.reverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> [a] -> [a]
L.take Int
1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
L.reverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
L.lines

-- | Get the first line in the string
firstLine :: String -> String
firstLine :: String -> String
firstLine = String -> String
strip forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
L.unlines forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> [a] -> [a]
L.take Int
1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
L.lines

-- | Trim leading and trailing whitespace and read the string into a value. Report the read value in the test
-- annotations.
readNoteM :: (Read a, Show a, H.MonadTest m, MonadCatch m, HasCallStack) => String -> m a
readNoteM :: forall a (m :: * -> *).
(Read a, Show a, MonadTest m, MonadCatch m, HasCallStack) =>
String -> m a
readNoteM String
inputStr =
  forall a. HasCallStack => (HasCallStack => a) -> a
withFrozenCallStack
  forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a.
(MonadTest m, MonadCatch m, HasCallStack, Show a) =>
m a -> m a
H.noteShowM
  forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) x a.
(MonadTest m, Show x, HasCallStack) =>
Either x a -> m a
H.evalEither
  forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (forall a. Semigroup a => a -> a -> a
<> String
": " forall a. Semigroup a => a -> a -> a
<> String
inputStr)
  forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Read a => String -> Either String a
readEither
  forall a b. (a -> b) -> a -> b
$ String -> String
strip String
inputStr