module ClassyPrelude
    ( 
      module CorePrelude
    , undefined
      
      
    , (++)
      
    , Semigroup (..)
    , WrappedMonoid
      
    , module Data.Functor
      
    , module Control.Applicative
      
    , module Control.Monad
    , whenM
    , unlessM
      
    , module Control.Concurrent.MVar.Lifted
    , module Control.Concurrent.Chan.Lifted
    , module Control.Concurrent.STM
    , atomically
    , alwaysSTM
    , alwaysSucceedsSTM
    , retrySTM
    , orElseSTM
    , checkSTM
    , module Data.IORef.Lifted
    , module Data.Mutable
      
    , PrimMonad
    , PrimState
    , primToPrim
    , primToIO
    , primToST
    , module Data.Primitive.MutVar
    , Prim
      
    , trace
    , traceShow
    , traceId
    , traceM
    , traceShowId
    , traceShowM
    , assert
      
    , module Data.Time
    , defaultTimeLocale
      
    , Generic
      
    , Identity (..)
    , MonadReader
    , ask
    , ReaderT (..)
    , Reader
      
    , module Data.Foldable
    , module Data.Traversable
      
    , module Data.Bifunctor
      
    , module Data.MonoTraversable
    , module Data.Sequences
    , module Data.Sequences.Lazy
    , module Data.Textual.Encoding
    , module Data.Containers
    , module Data.Builder
    , module Data.MinLen
    , module Data.ByteVector
      
    , Handle
    , stdin
    , stdout
    , stderr
      
      
    , map
    , concat
    , concatMap
    , foldMap
    , fold
    , length
    , null
    , pack
    , unpack
    , repack
    , toList
    , mapM_
    , sequence_
    , forM_
    , any
    , all
    , and
    , or
    , foldl'
    , foldr
    , foldM
    
    , readMay
    , intercalate
    , zip, zip3, zip4, zip5, zip6, zip7
    , unzip, unzip3, unzip4, unzip5, unzip6, unzip7
    , zipWith, zipWith3, zipWith4, zipWith5, zipWith6, zipWith7
    , hashNub
    , ordNub
    , ordNubBy
    , sortWith
    , compareLength
    , sum
    , product
    , Prelude.repeat
      
    , (\\)
    , intersect
    , unions
    
      
    , Show (..)
    , tshow
    , tlshow
      
    , charToLower
    , charToUpper
      
    , IOData (..)
    , print
    , hClose
      
    , fpToString
    , fpFromString
    , fpToText
    , fpFromText
    , fpToTextWarn
    , fpToTextEx
      
    , module Control.Exception.Enclosed
    , MonadThrow (throwM)
    , MonadCatch
    , MonadMask
      
      
    , asByteString
    , asLByteString
    , asHashMap
    , asHashSet
    , asText
    , asLText
    , asList
    , asMap
    , asIntMap
    , asMaybe
    , asSet
    , asIntSet
    , asVector
    , asUVector
    , asSVector
    , asString
    ) where
import qualified Prelude
import Control.Applicative ((<**>),liftA,liftA2,liftA3)
import Data.Functor
import Control.Exception (assert)
import Control.Exception.Enclosed
import Control.Monad (when, unless, void, liftM, ap, forever, join, replicateM_, guard, MonadPlus (..), (=<<), (>=>), (<=<), liftM2, liftM3, liftM4, liftM5)
import Control.Concurrent.MVar.Lifted
import Control.Concurrent.Chan.Lifted
import Control.Concurrent.STM hiding (atomically, always, alwaysSucceeds, retry, orElse, check)
import qualified Control.Concurrent.STM as STM
import Data.IORef.Lifted
import Data.Mutable
import qualified Data.Monoid as Monoid
import Data.Traversable (Traversable (..), for, forM)
import Data.Foldable (Foldable)
import Data.IOData (IOData (..))
import Control.Monad.Catch (MonadThrow (throwM), MonadCatch, MonadMask)
import Data.Vector.Instances ()
import CorePrelude hiding (print, undefined, (<>), catMaybes, first, second)
import Data.ChunkedZip
import qualified Data.Char as Char
import Data.Sequences
import Data.MonoTraversable
import Data.Containers
import Data.Builder
import Data.MinLen
import Data.ByteVector
import qualified Filesystem.Path.CurrentOS as F
import System.IO (Handle, stdin, stdout, stderr, hClose)
import Debug.Trace (trace, traceShow)
import Data.Semigroup (Semigroup (..), WrappedMonoid (..))
import Prelude (Show (..))
import Data.Time
    ( UTCTime (..)
    , Day (..)
    , toGregorian
    , fromGregorian
    , formatTime
    , parseTime
    , getCurrentTime
    )
import System.Locale (defaultTimeLocale)
import qualified Data.Set as Set
import qualified Data.Map as Map
import qualified Data.HashSet as HashSet
import Data.Textual.Encoding
import Data.Sequences.Lazy
import GHC.Generics (Generic)
import Control.Monad.Primitive (PrimMonad, PrimState, primToPrim, primToIO, primToST)
import Data.Primitive.MutVar
import Data.Primitive.Types (Prim)
import Data.Functor.Identity (Identity (..))
import Control.Monad.Reader (MonadReader, ask, ReaderT (..), Reader)
import Data.Bifunctor
tshow :: Show a => a -> Text
tshow = fromList . Prelude.show
tlshow :: Show a => a -> LText
tlshow = fromList . Prelude.show
charToLower :: Char -> Char
charToLower = Char.toLower
charToUpper :: Char -> Char
charToUpper = Char.toUpper
pack :: IsSequence c => [Element c] -> c
pack = fromList
unpack, toList :: MonoFoldable c => c -> [Element c]
unpack = otoList
toList = otoList
null :: MonoFoldable c => c -> Bool
null = onull
compareLength :: (Integral i, MonoFoldable c) => c -> i -> Ordering
compareLength = ocompareLength
sum :: (MonoFoldable c, Num (Element c)) => c -> Element c
sum = osum
product :: (MonoFoldable c, Num (Element c)) => c -> Element c
product = oproduct
all :: MonoFoldable c => (Element c -> Bool) -> c -> Bool
all = oall
any :: MonoFoldable c => (Element c -> Bool) -> c -> Bool
any = oany
and :: (MonoFoldable mono, Element mono ~ Bool) => mono -> Bool
and = oand
or :: (MonoFoldable mono, Element mono ~ Bool) => mono -> Bool
or = oor
length :: MonoFoldable c => c -> Int
length = olength
mapM_ :: (Monad m, MonoFoldable c) => (Element c -> m ()) -> c -> m ()
mapM_ = omapM_
forM_ :: (Monad m, MonoFoldable c) => c -> (Element c -> m ()) -> m ()
forM_ = oforM_
concatMap :: (Monoid m, MonoFoldable c) => (Element c -> m) -> c -> m
concatMap = ofoldMap
foldMap :: (Monoid m, MonoFoldable c) => (Element c -> m) -> c -> m
foldMap = ofoldMap
fold :: (Monoid (Element c), MonoFoldable c) => c -> Element c
fold = ofoldMap id
foldr :: MonoFoldable c => (Element c -> b -> b) -> b -> c -> b
foldr = ofoldr
foldl' :: MonoFoldable c => (a -> Element c -> a) -> a -> c -> a
foldl' = ofoldl'
foldM :: (Monad m, MonoFoldable c) => (a -> Element c -> m a) -> a -> c -> m a
foldM = ofoldlM
concat :: (MonoFoldable c, Monoid (Element c)) => c -> Element c
concat = ofoldMap id
readMay :: (Element c ~ Char, MonoFoldable c, Read a) => c -> Maybe a
readMay a = 
    case [x | (x, t) <- Prelude.reads (otoList a :: String), onull t] of
        [x] -> Just x
        _ -> Nothing
repack :: (MonoFoldable a, IsSequence b, Element a ~ Element b) => a -> b
repack = fromList . toList
map :: Functor f => (a -> b) -> f a -> f b
map = fmap
infixr 5  ++
(++) :: Monoid m => m -> m -> m
(++) = mappend
infixl 9 \\
(\\) :: SetContainer a => a -> a -> a
(\\) = difference
intersect :: SetContainer a => a -> a -> a
intersect = intersection
unions :: (MonoFoldable c, SetContainer (Element c)) => c -> Element c
unions = ofoldl' union Monoid.mempty
intercalate :: (Monoid (Element c), IsSequence c) => Element c -> c -> Element c
intercalate xs xss = concat (intersperse xs xss)
asByteString :: ByteString -> ByteString
asByteString = id
asLByteString :: LByteString -> LByteString
asLByteString = id
asHashMap :: HashMap k v -> HashMap k v
asHashMap = id
asHashSet :: HashSet a -> HashSet a
asHashSet = id
asText :: Text -> Text
asText = id
asLText :: LText -> LText
asLText = id
asList :: [a] -> [a]
asList = id
asMap :: Map k v -> Map k v
asMap = id
asIntMap :: IntMap v -> IntMap v
asIntMap = id
asMaybe :: Maybe a -> Maybe a
asMaybe = id
asSet :: Set a -> Set a
asSet = id
asIntSet :: IntSet -> IntSet
asIntSet = id
asVector :: Vector a -> Vector a
asVector = id
asUVector :: UVector a -> UVector a
asUVector = id
asSVector :: SVector a -> SVector a
asSVector = id
asString :: [Char] -> [Char]
asString = id
print :: (Show a, MonadIO m) => a -> m ()
print = liftIO . Prelude.print
sortWith :: (Ord a, IsSequence c) => (Element c -> a) -> c -> c
sortWith f = sortBy $ comparing f
undefined :: a
undefined = error "ClassyPrelude.undefined"
traceId :: String -> String
traceId a = trace a a
traceM :: (Monad m) => String -> m ()
traceM string = trace string $ return ()
traceShowId :: (Show a) => a -> a
traceShowId a = trace (show a) a
traceShowM :: (Show a, Monad m) => a -> m ()
traceShowM = traceM . show
fpToString :: FilePath -> String
fpToString = F.encodeString
fpFromString :: String -> FilePath
fpFromString = F.decodeString
fpToTextWarn :: MonadIO m => FilePath -> m Text
fpToTextWarn fp = case F.toText fp of
    Right ok -> return ok
    Left bad -> do
        putStrLn $ pack $ "non-unicode filepath: " ++ F.encodeString fp
        return bad
fpToTextEx :: FilePath -> Text
fpToTextEx fp = either (const $ error errorMsg) id $ F.toText fp
  where
    errorMsg = "fpToTextEx: non-unicode filepath: " ++ F.encodeString fp
fpToText :: FilePath -> Text
fpToText = either id id . F.toText
fpFromText :: Text -> FilePath
fpFromText = F.fromText
hashNub :: (Hashable a, Eq a) => [a] -> [a]
hashNub = go HashSet.empty
  where
    go _ []     = []
    go s (x:xs) | x `HashSet.member` s = go s xs
                | otherwise            = x : go (HashSet.insert x s) xs
ordNub :: (Ord a) => [a] -> [a]
ordNub = go Set.empty
  where
    go _ [] = []
    go s (x:xs) | x `Set.member` s = go s xs
                | otherwise        = x : go (Set.insert x s) xs
ordNubBy :: (Ord b) => (a -> b) -> (a -> a -> Bool) -> [a] -> [a]
ordNubBy p f = go Map.empty
  
  
  where
    go _ []     = []
    go m (x:xs) = let b = p x in case b `Map.lookup` m of
                    Nothing     -> x : go (Map.insert b [x] m) xs
                    Just bucket
                      | elem_by f x bucket -> go m xs
                      | otherwise          -> x : go (Map.insert b (x:bucket) m) xs
    
    elem_by :: (a -> a -> Bool) -> a -> [a] -> Bool
    elem_by _  _ []     = False
    elem_by eq y (x:xs) = y `eq` x || elem_by eq y xs
atomically :: MonadIO m => STM a -> m a
atomically = liftIO . STM.atomically
retrySTM :: STM a
retrySTM = STM.retry
alwaysSTM :: STM Bool -> STM ()
alwaysSTM = STM.always
alwaysSucceedsSTM :: STM a -> STM ()
alwaysSucceedsSTM = STM.alwaysSucceeds
orElseSTM :: STM a -> STM a -> STM a
orElseSTM = STM.orElse
checkSTM :: Bool -> STM ()
checkSTM = STM.check
whenM :: Monad m => m Bool -> m () -> m ()
whenM mbool action = mbool >>= flip when action
unlessM :: Monad m => m Bool -> m () -> m ()
unlessM mbool action = mbool >>= flip unless action
sequence_ :: (Monad m, MonoFoldable mono, Element mono ~ (m a)) => mono -> m ()
sequence_ = mapM_ (>> return ())