{-# LANGUAGE CPP #-}
module Freckle.App.Prelude
( module Prelude
, Alternative
, Generic
, HasCallStack
, Hashable
, HashMap
, HashSet
, Int64
, Map
, MonadIO
, MonadReader
, MonadUnliftIO
, NominalDiffTime
, NonEmpty
, PrimMonad
, ReaderT
, Set
, Text
, UTCTime
, Vector
, lift
, liftIO
, tshow
, pack
, unpack
, encodeUtf8
, decodeUtf8
, catMaybes
, fromMaybe
, isJust
, isNothing
, listToMaybe
, mapMaybe
, maybeToList
, module SafeAlternatives
, partitionEithers
, module Foldable
, module Traversable
, (<$$>)
, bimap
, first
, second
, (<|>)
, liftA2
, optional
, (<=<)
, (>=>)
, guard
, join
, unless
, void
, when
, (&&&)
, (***)
, getCurrentTime
, throwM
, throwString
, fromJustNoteM
, catch
, catchJust
, catches
, try
, tryJust
, impossible
, ExceptionHandler (..)
, Exception (displayException)
, SomeException (..)
) where
import Prelude hiding
( cycle
, foldl1
, foldr1
, head
, init
, last
#if MIN_VERSION_base(4,18,0)
, liftA2
#endif
, maximum
, minimum
, read
, tail
, (!!)
)
import Control.Applicative (Alternative, liftA2, optional, (<|>))
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Primitive (PrimMonad)
import Control.Monad.Reader (MonadReader, ReaderT)
import Data.HashMap.Strict (HashMap)
import Data.HashSet (HashSet)
import Data.Hashable (Hashable)
import Data.Int (Int64)
import Data.List.NonEmpty (NonEmpty)
import Data.Map.Strict (Map)
import Data.Set (Set)
import Data.Text (Text, pack, unpack)
import Data.Time (NominalDiffTime, UTCTime, getCurrentTime)
import Data.Vector (Vector)
import Freckle.App.Exception
import GHC.Generics (Generic)
import Data.Semigroup.Foldable as SafeAlternatives (fold1, foldMap1)
import Safe as SafeAlternatives
( atMay
, cycleMay
, headMay
, initMay
, lastMay
, maximumMay
, minimumMay
, readMay
, tailMay
)
import Control.Arrow ((&&&), (***))
import Control.Monad (guard, join, unless, void, when, (<=<), (>=>))
import Control.Monad.Trans (lift)
import Data.Bifunctor (bimap, first, second)
import Data.Either (partitionEithers)
import Data.Foldable as Foldable hiding (foldl1, foldr1)
import Data.Maybe
( catMaybes
, fromMaybe
, isJust
, isNothing
, listToMaybe
, mapMaybe
, maybeToList
)
import Data.Text.Encoding (decodeUtf8, encodeUtf8)
import Data.Traversable as Traversable
infixl 4 <$$>
(<$$>) :: (Functor c, Functor d) => (a -> b) -> c (d a) -> c (d b)
a -> b
f <$$> :: forall (c :: * -> *) (d :: * -> *) a b.
(Functor c, Functor d) =>
(a -> b) -> c (d a) -> c (d b)
<$$> c (d a)
as = (a -> b
f <$>) (d a -> d b) -> c (d a) -> c (d b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> c (d a)
as
tshow :: Show a => a -> Text
tshow :: forall a. Show a => a -> Text
tshow = String -> Text
pack (String -> Text) -> (a -> String) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> String
forall a. Show a => a -> String
show