-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | A typeclass-based Prelude. -- -- Modern best practices without name collisions. No partial functions -- are exposed, but modern data structures are, without requiring import -- lists. Qualified modules also are not needed: instead operations are -- based on type-classes from the mono-traversable package. @package classy-prelude @version 1.2.0.1 module ClassyPrelude -- | We define our own undefined which is marked as deprecated. This -- makes it useful to use during development, but lets you more easily -- get notifications if you accidentally ship partial code in production. -- -- The classy prelude recommendation for when you need to really have a -- partial function in production is to use error with a very -- descriptive message so that, in case an exception is thrown, you get -- more information than Prelude.undefined. -- -- Since 0.5.5 -- | Deprecated: It is highly recommended that you either avoid partial -- functions or provide meaningful error messages undefined :: HasCallStack => a (++) :: Monoid m => m -> m -> m infixr 5 ++ -- | The class of semigroups (types with an associative binary operation). class Semigroup a -- | An associative operation. -- --
-- (a <> b) <> c = a <> (b <> c) ---- -- If a is also a Monoid we further require -- --
-- (<>) = mappend --(<>) :: Semigroup a => a -> a -> a -- | Reduce a non-empty list with <> -- -- The default definition should be sufficient, but this can be -- overridden for efficiency. sconcat :: Semigroup a => NonEmpty a -> a -- | Repeat a value n times. -- -- Given that this works on a Semigroup it is allowed to fail if -- you request 0 or fewer repetitions, and the default definition will do -- so. -- -- By making this a member of the class, idempotent semigroups and -- monoids can upgrade this to execute in O(1) by picking -- stimes = stimesIdempotent or stimes = -- stimesIdempotentMonoid respectively. stimes :: (Semigroup a, Integral b) => b -> a -> a -- | Provide a Semigroup for an arbitrary Monoid. data WrappedMonoid m :: * -> * -- | && lifted to an Applicative. (<&&>) :: Applicative a => a Bool -> a Bool -> a Bool infixr 3 <&&> -- | || lifted to an Applicative. (<||>) :: Applicative a => a Bool -> a Bool -> a Bool infixr 2 <||> -- | Only perform the action if the predicate returns True. -- -- Since 0.9.2 whenM :: Monad m => m Bool -> m () -> m () -- | Only perform the action if the predicate returns False. -- -- Since 0.9.2 unlessM :: Monad m => m Bool -> m () -> m () -- | Generalized version of atomically. atomically :: MonadIO m => STM a -> m a -- | Synonym for always. alwaysSTM :: STM Bool -> STM () -- | Synonym for alwaysSucceeds. alwaysSucceedsSTM :: STM a -> STM () -- | Synonym for retry. retrySTM :: STM a -- | Synonym for orElse. orElseSTM :: STM a -> STM a -> STM a -- | Synonym for check. checkSTM :: Bool -> STM () -- | Convert a PrimBase to another monad with the same state token. primToPrim :: (PrimBase m1, PrimMonad m2, (~) * (PrimState m1) (PrimState m2)) => m1 a -> m2 a -- | Convert a PrimBase with a RealWorld state token to -- IO primToIO :: (PrimBase m, (~) * (PrimState m) RealWorld) => m a -> IO a -- | Convert a PrimBase to ST primToST :: PrimBase m => m a -> ST (PrimState m) a -- | The trace function outputs the trace message given as its first -- argument, before returning the second argument as its result. -- -- For example, this returns the value of f x but first outputs -- the message. -- --
-- trace ("calling f with x = " ++ show x) (f x)
--
--
-- The trace function should only be used for debugging, or
-- for monitoring execution. The function is not referentially
-- transparent: its type indicates that it is a pure function but it has
-- the side effect of outputting the trace message.
trace :: String -> a -> a
-- | Like trace, but uses show on the argument to convert it
-- to a String.
--
-- This makes it convenient for printing the values of interesting
-- variables or expressions inside a function. For example here we print
-- the value of the variables x and z:
--
-- -- f x y = -- traceShow (x, z) $ result -- where -- z = ... -- ... --traceShow :: Show a => a -> b -> b -- | Since 0.5.9 traceId :: String -> String -- | Since 0.5.9 traceM :: (Monad m) => String -> m () -- | Since 0.5.9 traceShowId :: (Show a) => a -> a -- | Since 0.5.9 traceShowM :: (Show a, Monad m) => a -> m () -- | If the first argument evaluates to True, then the result is the -- second argument. Otherwise an AssertionFailed exception is -- raised, containing a String with the source file and line -- number of the call to assert. -- -- Assertions can normally be turned on or off with a compiler flag (for -- GHC, assertions are normally on unless optimisation is turned on with -- -O or the -fignore-asserts option is given). When -- assertions are turned off, the first argument to assert is -- ignored, and the second argument is returned as the result. assert :: Bool -> a -> a -- | Locale representing American usage. -- -- knownTimeZones contains only the ten time-zones mentioned in -- RFC 822 sec. 5: "UT", "GMT", "EST", "EDT", "CST", "CDT", "MST", "MDT", -- "PST", "PDT". Note that the parsing functions will regardless parse -- single-letter military time-zones and +HHMM format. defaultTimeLocale :: TimeLocale -- | Representable types of kind *. This class is derivable in GHC with the -- DeriveGeneric flag on. class Generic a -- | Identity functor and monad. (a non-strict monad) newtype Identity a :: * -> * Identity :: a -> Identity a [runIdentity] :: Identity a -> a -- | See examples in Control.Monad.Reader. Note, the partially -- applied function type (->) r is a simple reader monad. See -- the instance declaration below. class Monad m => MonadReader r (m :: * -> *) | m -> r -- | Retrieves the monad environment. ask :: MonadReader r m => m r -- | Retrieves the monad environment. ask :: MonadReader r m => m r -- | Retrieves a function of the current environment. asks :: MonadReader r m => (r -> a) -> m a -- | The reader monad transformer, which adds a read-only environment to -- the given monad. -- -- The return function ignores the environment, while -- >>= passes the inherited environment to both -- subcomputations. newtype ReaderT k r (m :: k -> *) (a :: k) :: forall k. * -> (k -> *) -> k -> * ReaderT :: (r -> m a) -> ReaderT k r [runReaderT] :: ReaderT k r -> r -> m a -- | The parameterizable reader monad. -- -- Computations are functions of a shared environment. -- -- The return function ignores the environment, while -- >>= passes the inherited environment to both -- subcomputations. type Reader r = ReaderT * r Identity -- | Convert a ByteString into a storable Vector. toByteVector :: ByteString -> SVector Word8 -- | Convert a storable Vector into a ByteString. fromByteVector :: SVector Word8 -> ByteString -- | Haskell defines operations to read and write characters from and to -- files, represented by values of type Handle. Each value of -- this type is a handle: a record used by the Haskell run-time -- system to manage I/O with file system objects. A handle has at -- least the following properties: -- --
-- infixr 5 :^: -- data Tree a = Leaf a | Tree a :^: Tree a ---- -- the derived instance of Show is equivalent to -- --
-- instance (Show a) => Show (Tree a) where -- -- showsPrec d (Leaf m) = showParen (d > app_prec) $ -- showString "Leaf " . showsPrec (app_prec+1) m -- where app_prec = 10 -- -- showsPrec d (u :^: v) = showParen (d > up_prec) $ -- showsPrec (up_prec+1) u . -- showString " :^: " . -- showsPrec (up_prec+1) v -- where up_prec = 5 ---- -- Note that right-associativity of :^: is ignored. For example, -- --
-- showsPrec d x r ++ s == showsPrec d x (r ++ s) ---- -- Derived instances of Read and Show satisfy the -- following: -- -- -- -- That is, readsPrec parses the string produced by -- showsPrec, and delivers the value that showsPrec started -- with. showsPrec :: Show a => Int -> a -> ShowS -- | A specialised variant of showsPrec, using precedence context -- zero, and returning an ordinary String. show :: Show a => a -> String -- | The method showList is provided to allow the programmer to give -- a specialised way of showing lists of values. For example, this is -- used by the predefined Show instance of the Char type, -- where values of type String should be shown in double quotes, -- rather than between square brackets. showList :: Show a => [a] -> ShowS tshow :: Show a => a -> Text tlshow :: Show a => a -> LText -- | Convert a character to lower case. -- -- Character-based case conversion is lossy in comparison to string-based -- toLower. For instance, İ will be converted to i, instead of i̇. charToLower :: Char -> Char -- | Convert a character to upper case. -- -- Character-based case conversion is lossy in comparison to string-based -- toUpper. For instance, ß won't be converted to SS. charToUpper :: Char -> Char -- | Strictly read a file into a ByteString. readFile :: MonadIO m => FilePath -> m ByteString -- | Strictly read a file into a Text using a UTF-8 character -- encoding. In the event of a character encoding error, a Unicode -- replacement character will be used (a.k.a., lenientDecode). readFileUtf8 :: MonadIO m => FilePath -> m Text -- | Write a ByteString to a file. writeFile :: MonadIO m => FilePath -> ByteString -> m () -- | Write a Text to a file using a UTF-8 character encoding. writeFileUtf8 :: MonadIO m => FilePath -> Text -> m () -- | Strictly read the contents of the given Handle into a -- ByteString. hGetContents :: MonadIO m => Handle -> m ByteString -- | Write a ByteString to the given Handle. hPut :: MonadIO m => Handle -> ByteString -> m () -- | Read a single chunk of data as a ByteString from the given -- Handle. -- -- Under the surface, this uses hGetSome with the default chunk -- size. hGetChunk :: MonadIO m => Handle -> m ByteString print :: (Show a, MonadIO m) => a -> m () -- | Computation hClose hdl makes handle hdl -- closed. Before the computation finishes, if hdl is writable -- its buffer is flushed as for hFlush. Performing hClose -- on a handle that has already been closed has no effect; doing so is -- not an error. All other operations on a closed handle will fail. If -- hClose fails for any reason, any further operations (apart from -- hClose) on the handle will still fail as if hdl had -- been successfully closed. hClose :: Handle -> IO () -- | A difference list is a function that, given a list, returns the -- original contents of the difference list prepended to the given list. -- -- This structure supports O(1) append and snoc operations on -- lists, making it very useful for append-heavy uses (esp. left-nested -- uses of ++), such as logging and pretty printing. -- -- Here is an example using DList as the state type when printing a tree -- with the Writer monad: -- --
-- import Control.Monad.Writer -- import Data.DList -- -- data Tree a = Leaf a | Branch (Tree a) (Tree a) -- -- flatten_writer :: Tree x -> DList x -- flatten_writer = snd . runWriter . flatten -- where -- flatten (Leaf x) = tell (singleton x) -- flatten (Branch x y) = flatten x >> flatten y --data DList a :: * -> * -- | Force type to a DList -- -- Since 0.11.0 asDList :: DList a -> DList a -- | Synonym for apply -- -- Since 0.11.0 applyDList :: DList a -> [a] -> [a] asByteString :: ByteString -> ByteString asLByteString :: LByteString -> LByteString asHashMap :: HashMap k v -> HashMap k v asHashSet :: HashSet a -> HashSet a asText :: Text -> Text asLText :: LText -> LText asList :: [a] -> [a] asMap :: Map k v -> Map k v asIntMap :: IntMap v -> IntMap v asMaybe :: Maybe a -> Maybe a asSet :: Set a -> Set a asIntSet :: IntSet -> IntSet asVector :: Vector a -> Vector a asUVector :: UVector a -> UVector a asSVector :: SVector a -> SVector a asString :: [Char] -> [Char]