{-# OPTIONS_GHC -Wno-redundant-constraints #-}
module Imports
(
module Prelude,
module Control.Applicative,
module Control.Monad,
module Data.Functor,
module Data.Bifunctor,
module Data.Function,
module Data.Functor.Identity,
module Data.Int,
module Data.Word,
module Data.Void,
module Data.Bool,
module Data.Char,
module Data.Ord,
module Data.Semigroup,
module Data.Monoid,
module Data.Maybe,
module Data.Either,
module Data.Either.Combinators,
module Data.Foldable,
module Data.Traversable,
module Data.Tuple,
module Data.String,
module Data.List,
Generic,
Typeable,
HasCallStack,
readMaybe,
readEither,
module Control.Monad.Trans,
module Control.Monad.Reader.Class,
module Control.Monad.Trans.Reader,
module Control.Monad.IO.Unlift,
module Control.DeepSeq,
module UnliftIO.IO,
module UnliftIO.Directory,
putStr,
putStrLn,
print,
getLine,
readFile,
writeFile,
appendFile,
getArgs,
getEnv,
lookupEnv,
setEnv,
unsetEnv,
ThreadId,
forkIO,
forkOS,
killThread,
threadDelay,
module UnliftIO.IORef,
module UnliftIO.MVar,
Exception (..),
SomeException (..),
SomeAsyncException (..),
IOException,
module UnliftIO.STM,
Map,
Set,
HashMap,
HashSet,
ByteString,
LByteString,
Text,
LText,
whenM,
unlessM,
(<$$>),
(<$$$>),
todo,
pattern TODO,
TodoException (..),
)
where
import Control.Applicative hiding (empty, many, optional, some)
import Control.DeepSeq (NFData (..), deepseq)
import Control.Exception
import Control.Monad hiding (forM, forM_, mapM, mapM_, msum, sequence, sequence_)
import Control.Monad.Extra (unlessM, whenM)
import Control.Monad.IO.Unlift
import Control.Monad.Reader.Class
import Control.Monad.Trans
import Control.Monad.Trans.Reader
( Reader,
ReaderT (ReaderT),
mapReader,
mapReaderT,
runReader,
runReaderT,
withReader,
withReaderT,
)
import Data.Bifunctor hiding (first, second)
import Data.Bool
import Data.ByteString (ByteString)
import Data.ByteString.Lazy qualified
import Data.Char
import Data.Either
import Data.Either.Combinators hiding (fromLeft, fromRight, isLeft, isRight)
import Data.Foldable
import Data.Function
import Data.Functor
import Data.Functor.Identity
import Data.HashMap.Strict (HashMap)
import Data.HashSet (HashSet)
import Data.Int
import Data.Kind (Type)
import Data.List hiding (delete, insert, singleton)
import Data.Map (Map)
import Data.Maybe
import Data.Monoid hiding (First (..), Last (..))
import Data.Ord
import Data.Semigroup hiding (diff)
import Data.Set (Set)
import Data.String
import Data.Text (Text)
import Data.Text.Lazy qualified
import Data.Traversable
import Data.Tuple
import Data.Void
import Data.Word
import GHC.Exts
import GHC.Generics (Generic)
import GHC.Stack (HasCallStack)
import Text.Read (readEither, readMaybe)
import UnliftIO.Concurrent
import UnliftIO.Directory hiding (Permissions)
import UnliftIO.Environment
import UnliftIO.Exception
import UnliftIO.IO hiding (Handle, getMonotonicTime)
import UnliftIO.IORef
import UnliftIO.MVar
import UnliftIO.STM
import Prelude
( Bounded (..),
Double,
Enum (..),
Eq (..),
FilePath,
Float,
Floating (..),
Fractional (..),
IO,
Integer,
Integral (..),
Num (..),
Ord (..),
Rational,
Read (..),
ReadS,
Real (..),
RealFloat (..),
RealFrac (..),
Show (..),
ShowS,
error,
even,
fromIntegral,
gcd,
lcm,
lex,
odd,
read,
readParen,
reads,
realToFrac,
seq,
showChar,
showParen,
showString,
shows,
subtract,
undefined,
($!),
(^),
(^^),
)
import Prelude qualified as P
type LText = Data.Text.Lazy.Text
type LByteString = Data.ByteString.Lazy.ByteString
putStr :: (MonadIO m) => String -> m ()
putStr :: forall (m :: * -> *). MonadIO m => String -> m ()
putStr = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> (String -> IO ()) -> String -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO ()
P.putStr
putStrLn :: (MonadIO m) => String -> m ()
putStrLn :: forall (m :: * -> *). MonadIO m => String -> m ()
putStrLn = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> (String -> IO ()) -> String -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO ()
P.putStrLn
print :: (Show a, MonadIO m) => a -> m ()
print :: forall a (m :: * -> *). (Show a, MonadIO m) => a -> m ()
print = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> (a -> IO ()) -> a -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> IO ()
forall a. Show a => a -> IO ()
P.print
getLine :: (MonadIO m) => m String
getLine :: forall (m :: * -> *). MonadIO m => m String
getLine = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO String
P.getLine
readFile :: (MonadIO m) => FilePath -> m String
readFile :: forall (m :: * -> *). MonadIO m => String -> m String
readFile = IO String -> m String
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String)
-> (String -> IO String) -> String -> m String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO String
P.readFile
writeFile :: (MonadIO m) => FilePath -> String -> m ()
writeFile :: forall (m :: * -> *). MonadIO m => String -> String -> m ()
writeFile = (IO () -> m ()) -> (String -> IO ()) -> String -> m ()
forall a b. (a -> b) -> (String -> a) -> String -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO ((String -> IO ()) -> String -> m ())
-> (String -> String -> IO ()) -> String -> String -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> IO ()
P.writeFile
appendFile :: (MonadIO m) => FilePath -> String -> m ()
appendFile :: forall (m :: * -> *). MonadIO m => String -> String -> m ()
appendFile = (IO () -> m ()) -> (String -> IO ()) -> String -> m ()
forall a b. (a -> b) -> (String -> a) -> String -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO ((String -> IO ()) -> String -> m ())
-> (String -> String -> IO ()) -> String -> String -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> IO ()
P.appendFile
todo :: forall {r :: RuntimeRep} (a :: TYPE r). (HasCallStack) => a
todo :: forall a. HasCallStack => a
todo = TodoException -> a
forall a e. Exception e => e -> a
throw TodoException
TodoException
{-# WARNING todo "'todo' left in code" #-}
pattern TODO :: forall (a :: Type). (HasCallStack) => forall. a
pattern $mTODO :: forall {r} {a}.
HasCallStack =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
$bTODO :: forall a. HasCallStack => a
TODO <- (throw TodoException -> !_unused)
where
TODO = TodoException -> a
forall a e. Exception e => e -> a
throw TodoException
TodoException
{-# WARNING TODO "'TODO' left in code" #-}
{-# COMPLETE TODO #-}
data TodoException = TodoException
deriving stock (TodoException -> TodoException -> Bool
(TodoException -> TodoException -> Bool)
-> (TodoException -> TodoException -> Bool) -> Eq TodoException
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TodoException -> TodoException -> Bool
== :: TodoException -> TodoException -> Bool
$c/= :: TodoException -> TodoException -> Bool
/= :: TodoException -> TodoException -> Bool
Eq, Int -> TodoException -> ShowS
[TodoException] -> ShowS
TodoException -> String
(Int -> TodoException -> ShowS)
-> (TodoException -> String)
-> ([TodoException] -> ShowS)
-> Show TodoException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TodoException -> ShowS
showsPrec :: Int -> TodoException -> ShowS
$cshow :: TodoException -> String
show :: TodoException -> String
$cshowList :: [TodoException] -> ShowS
showList :: [TodoException] -> ShowS
Show)
instance Exception TodoException where
displayException :: TodoException -> String
displayException TodoException
_ = String
"Develop.Placeholder.todo: not yet implemented"
(<$$>) :: (Functor f, Functor g) => (a -> b) -> f (g a) -> f (g b)
<$$> :: forall (f :: * -> *) (g :: * -> *) a b.
(Functor f, Functor g) =>
(a -> b) -> f (g a) -> f (g b)
(<$$>) = (g a -> g b) -> f (g a) -> f (g b)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((g a -> g b) -> f (g a) -> f (g b))
-> ((a -> b) -> g a -> g b) -> (a -> b) -> f (g a) -> f (g b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b) -> g a -> g b
forall a b. (a -> b) -> g a -> g b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
infix 4 <$$>
(<$$$>) :: (Functor f, Functor g, Functor h) => (a -> b) -> f (g (h a)) -> f (g (h b))
<$$$> :: forall (f :: * -> *) (g :: * -> *) (h :: * -> *) a b.
(Functor f, Functor g, Functor h) =>
(a -> b) -> f (g (h a)) -> f (g (h b))
(<$$$>) = (g (h a) -> g (h b)) -> f (g (h a)) -> f (g (h b))
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((g (h a) -> g (h b)) -> f (g (h a)) -> f (g (h b)))
-> ((a -> b) -> g (h a) -> g (h b))
-> (a -> b)
-> f (g (h a))
-> f (g (h b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (h a -> h b) -> g (h a) -> g (h b)
forall a b. (a -> b) -> g a -> g b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((h a -> h b) -> g (h a) -> g (h b))
-> ((a -> b) -> h a -> h b) -> (a -> b) -> g (h a) -> g (h b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b) -> h a -> h b
forall a b. (a -> b) -> h a -> h b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
infix 4 <$$$>