{-# OPTIONS_GHC -fno-warn-orphans #-}

module Hydrogen.Prelude (
    module Prelude
  , module Control.Applicative
  , module Control.Arrow
  , module Control.Monad
  , module Data.Array
  , module Data.Bits
  , module Data.Bool
  , module Data.Char
  , module Data.Complex
  , module Data.Dynamic
  , module Data.Either
  , module Data.Fixed
  , module Data.Function
  , module Data.Functor.Identity
  , module Data.Functor.Reverse
  , module Data.Hashable
  , module Data.Foldable
  , module Data.Int
  , module Data.Ix
  , module Data.List
  , module Data.Maybe
  , module Data.Ord
  , module Data.Ratio
  , module Data.Serialize
  , module Data.String
  , module Data.Time
  , module Data.Tuple
  , module Data.Typeable
  , module Data.Word
  , module Hydrogen.Version
  , module Numeric
  , module Text.Printf
  , (.&), (.|), (=~), (=~~)
  , for
  , Generic, Map, Set
  ) where

import "base" Prelude hiding (
    all
  , and
  , any
  , concat
  , concatMap
  , elem
  , foldl
  , foldl1
  , foldr
  , foldr1
  , mapM_
  , maximum
  , minimum
  , notElem
  , or
  , product
  , sequence_
  , sum
  )

import "base" Control.Applicative
import "base" Control.Arrow
import "base" Control.Monad hiding (
    forM_
  , mapM_
  , msum
  , sequence_
  )

import "array" Data.Array

import "base" Data.Bits hiding (bitSize)
import "base" Data.Bool
import "base" Data.Char
import "base" Data.Complex
import "base" Data.Dynamic
import "base" Data.Either
import "base" Data.Fixed
import "base" Data.Foldable
import "base" Data.Function
import "transformers" Data.Functor.Identity (Identity (..))
import "transformers" Data.Functor.Reverse (Reverse (..))
import "hashable" Data.Hashable
import "base" Data.Int
import "base" Data.Ix
import "base" Data.List hiding (
    all
  , and
  , any
  , concat
  , concatMap
  , elem
  , find
  , foldl
  , foldl'
  , foldl1
  , foldr
  , foldr1
  , maximum
  , minimum
  , maximumBy
  , minimumBy
  , notElem
  , or
  , product
  , sum
  )
import "base" Data.Maybe
import "base" Data.Ord
import "base" Data.Ratio
import "cereal" Data.Serialize
import "base" Data.String
import "time" Data.Time
import "base" Data.Tuple
import "base" Data.Typeable
import "base" Data.Word

import "base" GHC.Generics

import "base" Numeric

import "base" Text.Printf
import "regex-tdfa" Text.Regex.TDFA

import "containers" Data.Map (Map)
import "containers" Data.Set (Set)

import "hydrogen-version" Hydrogen.Version

deriving instance Eq ZonedTime

data ShowBox where
    ShowBox :: forall a. (Show a) => a -> ShowBox

instance Show ShowBox where
    show (ShowBox a) = show a

(.|), (.&) :: (a -> Bool) -> (a -> Bool) -> (a -> Bool)
f .| g = \x -> f x || g x
f .& g = \x -> f x && g x

for :: Functor f => f a -> (a -> b) -> f b
for = flip fmap

__ :: a
__ = error "Hydrogen.Prelude.undefined"