{-# 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 , uuidFromString , randomUUID , safeHead , UUID , Generic , List , Map , Set , Seq , ShowBox , TMap (..) , Has (..) , __ ) 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 hiding ((!)) import qualified "array" Data.Array as 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 (Generic) import "base" Numeric import "base" Text.Printf import "regex-tdfa" Text.Regex.TDFA import "containers" Data.Map (Map) import qualified "containers" Data.Map as Map import "containers" Data.Set (Set) -- import qualified "containers" Data.Set as Set import "containers" Data.Sequence (Seq) -- import qualified "containers" Data.Sequence as Seq import "hydrogen-version" Hydrogen.Version import "uuid" Data.UUID (UUID) import qualified "uuid" Data.UUID import qualified "uuid" Data.UUID.V4 deriving instance Eq ZonedTime deriving instance Generic Day deriving instance Generic LocalTime deriving instance Generic TimeZone deriving instance Generic TimeOfDay deriving instance Generic UniversalTime deriving instance Generic ZonedTime instance Serialize Day instance Serialize LocalTime instance Serialize TimeOfDay instance Serialize TimeZone instance Serialize UniversalTime instance Serialize Version instance Serialize ZonedTime instance Serialize (Fixed E12) where put (MkFixed int) = put int get = MkFixed <$> get instance Serialize UUID where put uuid = do let p = putWord32be (w1, w2, w3, w4) = Data.UUID.toWords uuid p w1 >> p w2 >> p w3 >> p w4 get = let g = getWord32be in liftM4 Data.UUID.fromWords g g g g 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 (|>) :: a -> (a -> b) -> b (|>) = flip ($) for :: Functor f => f a -> (a -> b) -> f b for = flip fmap __ :: a __ = error "Hydrogen.Prelude.undefined" uuidFromString :: String -> Maybe UUID uuidFromString = Data.UUID.fromString randomUUID :: IO UUID randomUUID = Data.UUID.V4.nextRandom safeHead :: a -> [a] -> a safeHead d = \case x : _ -> x _ -> d class TMap a where type Component x type Transform x tmap :: (Component a -> b) -> a -> Transform ((Component a -> b) -> a) instance TMap (a, a) where type Component (a, a) = a type Transform ((a -> b) -> (a, a)) = (b, b) tmap f (a, b) = (f a, f b) instance TMap (a, a, a) where type Component (a, a, a) = a type Transform ((a -> b) -> (a, a, a)) = (b, b, b) tmap f (a, b, c) = (f a, f b, f c) instance TMap (a, a, a, a) where type Component (a, a, a, a) = a type Transform ((a -> b) -> (a, a, a, a)) = (b, b, b, b) tmap f (a, b, c, d) = (f a, f b, f c, f d) instance TMap [a] where type Component [a] = a type Transform ((a -> b) -> [a]) = [b] tmap = map instance TMap (Map k v) where type Component (Map k v) = v type Transform ((v -> w) -> Map k v) = Map k w tmap = Map.map instance TMap (Seq a) where type Component (Seq a) = a type Transform ((a -> b) -> Seq a) = Seq b tmap = fmap type List a = [a] class Has a where type K a type V a (!) :: a -> K a -> V a instance Ord k => Has (Map k v) where type K (Map k v) = k type V (Map k v) = v (!) = (Map.!) instance Eq k => Has [(k, v)] where type K [(k, v)] = k type V [(k, v)] = v list ! key = maybeKey (lookup key list) where maybeKey = maybe (error "Hydrogen.Prelude.! key not found") id instance Ix i => Has (Array i e) where type K (Array i e) = i type V (Array i e) = e (!) = (Array.!)