{-# LANGUAGE CPP #-}
module Global (
Proxy(..)
, Map, Set
, IntMap, IntSet
, HashMap, HashSet
, (<|>)
, first, second, bimap
, Monoid(..), Semigroup(..)
, while, while_
, allM, anyM, ifM, andM, orM
, findM, partitionM
, unlessM, whenM, whenJust, whenJustM
, foldl'
, mconcatMap, concatMapM, mapMaybeM
, mapMaybe, fromMaybe
, justm, rightm
, firstJust, firstJusts
, errorStack, errorIO
, justErr, tryJust, tryRight
, Pretty, pretty, prettys
, Lens, (#)
, (#$), (#=), (%=)
, (<#>)
, module Control.Monad
, module Data.Traversable
, module Data.Foldable
, MonadIO, lift, liftIO
, NonEmpty((:|))
, Text.Text
, txt, untxt, showt
) where
import Control.Applicative ((<|>))
import Control.Monad
(ap, filterM, foldM, forM, forM_, forever, guard, liftM, mplus, msum, mzero,
replicateM, replicateM_, unless, void, when, zipWithM, zipWithM_, (<=<),
(>=>))
import Control.Monad.Trans (MonadIO, lift, liftIO)
import Data.Foldable (Foldable, foldMap)
import Data.HashMap.Strict (HashMap)
import Data.HashSet (HashSet)
import Data.IntMap (IntMap)
import Data.IntSet (IntSet)
import Data.List (foldl')
import Data.List.NonEmpty (NonEmpty((:|)))
import Data.Map (Map)
import Data.Maybe (fromMaybe, mapMaybe)
import Data.Proxy (Proxy(..))
import Data.Semigroup (Semigroup(..))
import Data.Set (Set)
import qualified Data.Text as Text
import Data.Traversable (Traversable, traverse)
import Util.Pretty (Pretty, pretty, prettys)
import Util.Control
import Util.Lens
txt :: String -> Text.Text
txt :: String -> Text
txt = String -> Text
Text.pack
untxt :: Text.Text -> String
untxt :: Text -> String
untxt = Text -> String
Text.unpack
showt :: Show a => a -> Text.Text
showt :: forall a. Show a => a -> Text
showt = String -> Text
txt forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show