{- |
Module      : Antelude
Description : Yet another alternative Prelude for Haskell
Copyright   : (c) David Neave, 2024
License     : MIT
Maintainer  : dneavesdev@pm.me
This is just what's available in the global scope. It is intended this way to encourage qualified or named-exposure imports, to give clarity to everyone reading your code where something came from.

For everything else you require, you are encouraged to:

* See if there's an Antelude module containing what you're looking for (ex.: Antelude.List: 'Antelude.List')

* See if there's a base package containing what you're looking for (ex.: Data.Char: 'Data.Char', Control.Applicative: 'Control.Applicative')

* See if there's an external package containing what you're looking for (ex.: Data.Text.Lazy.IO: 'Data.Text.Lazy.IO' from the "text" package)
-}
module Antelude
    ( -- * Symbols and Functions
      -- ** Symbols
      -- *** Function Piping and Composition
      (.>)
    , (<.)
    , (<|)
    , (|>)
      -- *** Monadic Stuff
      -- | Reexport from 'Control.Monad'
    , (=<<)
      -- | Reexport from 'Control.Monad'
    , (<<)
    , (>=>)
      -- | Reexport from 'Control.Monad'
    , (<=<)
      -- *** Boolean
      -- | Reexport from 'Data.Bool'
    , (&&)
      -- | Reexport from 'Data.Bool'
    , (||)
      -- *** Functors
      -- | Reexport from 'Data.Functor'
    , ($>)
      -- | Reexport from 'Data.Functor'
    , (<$>)
      -- | Reexport from 'Data.Functor'
    , (<&>)
      -- *** Numeric Non-Class
      -- | Reexport from 'Prelude'
    , (^)
      -- | Reexport from 'Prelude'
    , (^^)
      -- *** Strictly Apply
      -- | Reexport from 'Prelude'
    , ($!)
      -- ** Functions
      -- | Often used as a catch-all case for multi-way-ifs and guards. Is always 'True'.
    , ABool.otherwise
      -- | 'Show'/'print' something to stdout.
    , Pre.print
      -- * Types and Classes
      -- ** Types
      -- *** Basics
      -- | Reexport from 'Data.Bool'
    , Bool (..)
      -- | Reexport from 'Data.Char'
    , Char
      -- | Reexport from 'Data.String'
    , String
      -- | Reexport from 'Data.Int'
    , Int
      -- | Reexport from 'Prelude'
    , Integer
      -- | Reexport from 'Prelude'
    , Float
      -- | Reexport from 'Prelude'
    , Double
      -- | Reexport from 'Data.Ratio'
    , Rational
      -- | Reexport from 'Data.Word'
    , Word
      -- *** Container-Types
      -- **** List and List-ish
      -- | Reexport from 'Data.List'
    , List
      -- | Reexport from 'Data.List.NonEmpty'
    , NonEmpty (..)
      -- | Reexport from 'Data.Array' of the "array" package
    , Array
      -- **** Formally-Named Tuples
    , Pair
    , Trio
      -- *** External-Package-Types
    , ByteString
    , ByteStringLazy
    , Map
    , MapLazy
    , Text
    , TextLazy
      -- | Reexport from 'Data.Set' of the "containers" package
    , Set
      -- | Reexport from 'Data.Sequence' of the "containers" package
    , Seq
      -- *** Other Important Things
      -- | Reexport from 'Data.Maybe'
    , Maybe (..)
      -- | Reexport from 'Data.Either'
    , Either (..)
    , Result (..)
      -- | Reexport from 'Data.Ord'
    , Ordering (..)
      -- | Reexport from 'Text.Show'
    , ShowS
      -- | Reexport from 'Text.Read'
    , ReadS
      -- | Reexport from 'System.IO'
    , IO
      -- | Reexport from 'System.IO'
    , FilePath
      -- | Reexport from 'System.IO.Error'
    , IOError
      -- | Reexport from 'Data.Void'
    , Void
      -- ** Classes
      -- *** Numeric Classes
      -- | Reexport from 'Prelude'
    , Num ((+), (-), (*))
      -- | Reexport from 'Prelude'
    , Real
      -- | Reexport from 'Prelude'
    , Integral
      -- | Reexport from 'Prelude'
    , Fractional ((/))
      -- | Reexport from 'Prelude'
    , Floating ((**))
      -- | Reexport from 'Prelude'
    , RealFrac
      -- | Reexport from 'Prelude'
    , RealFloat
      -- *** The "Theorum-Based" Classes
      -- | Reexport from 'Data.Semigroup'
    , Semigroup ((<>))
      -- | Reexport from 'Data.Monoid'
    , Monoid
      -- | Reexport from 'Control.Monad'
    , Functor (..)
      -- | Reexport from 'Control.Applicative'
    , Alternative (empty, (<|>))
    , Applicative (..)
      -- | Reexport from 'Control.Monad'
    , Monad (..)
      -- | Reexport from 'Control.Monad.IO.Class'
    , MonadIO (..)
      -- | Reexport from 'Control.Monad'
    , MonadPlus
      -- | Reexport from 'Control.Monad.Fail'
    , MonadFail
      -- *** The Rest of the Classes
      -- | Reexport from 'Data.Eq'
    , Eq (..)
      -- | Reexport from 'Data.Ord'
    , Ord ((<), (>), (<=), (>=))
      -- | Reexport from 'Prelude'
    , Enum
      -- | Reexport from 'Prelude'
    , Bounded
      -- | Reexport from 'Data.Foldable'
    , Foldable
      -- | Reexport from 'Data.Traversable'
    , Traversable
      -- | Reexport from 'Text.Show'
    , Show (show, showList)
      -- | Reexport from 'Text.Read'
    , Read
    ) where

import safe           Antelude.Bool                  as ABool
    ( otherwise
    , (&&)
    , (||)
    )
import safe           Antelude.Function              as AFunc
    ( (.>)
    , (<.)
    , (<|)
    , (|>)
    )
import safe           Antelude.Internal.TypesClasses as AITC
    ( Alternative (empty, (<|>))
    , Applicative (..)
    , Array
    , Bool (..)
    , Bounded
    , ByteString
    , ByteStringLazy
    , Char
    , Double
    , Either (..)
    , Enum
    , Eq (..)
    , FilePath
    , Float
    , Floating ((**))
    , Foldable
    , Fractional ((/))
    , Functor (..)
    , IO
    , IOError
    , Int
    , Integer
    , Integral
    , List
    , Map
    , MapLazy
    , Maybe (..)
    , Monad (..)
    , MonadFail
    , MonadIO (..)
    , MonadPlus
    , Monoid
    , NonEmpty (..)
    , Num ((*), (+), (-))
    , Ord ((<), (<=), (>), (>=))
    , Ordering (..)
    , Pair
    , Rational
    , Read
    , ReadS
    , Real
    , RealFloat
    , RealFrac
    , Result (..)
    , Semigroup ((<>))
    , Seq
    , Set
    , Show (show, showList)
    , ShowS
    , String
    , Text
    , TextLazy
    , Traversable
    , Trio
    , Void
    , Word
    )
import safe           Antelude.Monad                 as AMonad
    ( ($>)
    , (<<)
    , (<=<)
    , (=<<)
    , (>=>)
    )

import safe           Data.Functor                   ( (<$>), (<&>) )

import safe           Prelude                        as Pre
    ( print
    , ($!)
    , (^)
    , (^^)
    )