{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} -- | Local Prelude. -- module Preamble.Prelude ( module Exports , runResourceT , maybe' , either' , maybe_ , eitherThrowIO , maybeThrowIO , boolThrowIO , textFromString , (-/-) , (-.-) , (-:-) ) where import BasicPrelude as Exports hiding (bool) import Control.Lens as Exports hiding (uncons, (.=), (<.>)) import Control.Monad.Trans.Resource import Data.Bool as Exports import Data.Text import Safe as Exports (headMay, initMay, tailMay) -- | maybe with hanging function. -- maybe' :: Maybe a -> b -> (a -> b) -> b maybe' m b a = maybe b a m -- | either with hanging function. -- either' :: Either a b -> (a -> c) -> (b -> c) -> c either' e b a = either b a e -- | Maybe that returns () if Nothing -- maybe_ :: Monad m => Maybe a -> (a -> m ()) -> m () maybe_ = flip $ maybe $ return () -- | Throw userError on either error. -- eitherThrowIO :: MonadIO m => Either String a -> m a eitherThrowIO = either (liftIO . throwIO . userError) return -- | Throw userError on maybe nothing. -- maybeThrowIO :: MonadIO m => String -> Maybe a -> m a maybeThrowIO s = maybe (liftIO $ throwIO $ userError s) return -- | Throw userError on false. -- boolThrowIO :: MonadIO m => String -> Bool -> m () boolThrowIO = flip unless . liftIO . throwIO . userError -- | Reverse of textToString -- textFromString :: String -> Text textFromString = pack -- | for IsString. -- (-/-) :: (IsString s, Monoid s) => s -> s -> s (-/-) = (<>) . (<> "/") -- | <.> for IsString. -- (-.-) :: (IsString s, Monoid s) => s -> s -> s (-.-) = (<>) . (<> ".") -- | <:> for IsString. -- (-:-) :: (IsString s, Monoid s) => s -> s -> s (-:-) = (<>) . (<> ":")