| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Prelude.Spiros.Utilities
Description
Utilities.
These identifiers are "soft" overrides, they generalize the signatures of their Prelude namesakes:
These symbols are "hard" overrides, they are completely different from Prelude:
Synopsis
- newtype Time = Time {}
 - map :: Functor f => (a -> b) -> f a -> f b
 - sequence :: (Traversable t, Applicative f) => t (f a) -> f (t a)
 - sequence_ :: (Foldable t, Applicative f) => t (f a) -> f ()
 - (>) :: (a -> b) -> (b -> c) -> a -> c
 - (<) :: (b -> c) -> (a -> b) -> a -> c
 - lessThan :: Ord a => a -> a -> Bool
 - greaterThan :: Ord a => a -> a -> Bool
 - (-:) :: a -> b -> (a, b)
 - todo :: a
 - __BUG__ :: SomeException -> a
 - __ERROR__ :: String -> a
 - errorM :: MonadThrow m => String -> m a
 - nothing :: Applicative m => m ()
 - returning :: Applicative m => (a -> b) -> a -> m b
 - maybe2bool :: Maybe a -> Bool
 - maybe2either :: e -> Maybe a -> Either e a
 - either2maybe :: Either e a -> Maybe a
 - either2bool :: Either e a -> Bool
 - maybe2list :: Maybe a -> [a]
 - list2maybe :: [a] -> Maybe a
 - nonempty2list :: NonEmpty a -> [a]
 - list :: r -> (a -> [a] -> r) -> [a] -> r
 - unsafeNatural :: Integral i => i -> Natural
 - ratio :: Integral a => a -> a -> Ratio a
 - ($>) :: Functor f => f a -> b -> f b
 - (<&>) :: Functor f => f a -> (a -> b) -> f b
 - ordNub :: Ord a => [a] -> [a]
 - ordNubBy :: Ord b => (a -> b) -> [a] -> [a]
 - nth :: Natural -> [a] -> Maybe a
 - snoc :: [a] -> a -> [a]
 - toInt :: Integral a => a -> Int
 - strip :: String -> String
 - lstrip :: String -> String
 - rstrip :: String -> String
 - shown :: forall a t. (Show a, IsString t) => a -> t
 - constructors :: BoundedEnum a => proxy a -> [a]
 - constructors' :: forall a. BoundedEnum a => [a]
 - identity :: Category cat => a `cat` a
 - compose :: Category cat => (b `cat` c) -> (a `cat` b) -> a `cat` c
 - typeName :: forall proxy a t. (Typeable a, IsString t) => proxy a -> t
 - whenM :: Monad m => m Bool -> m () -> m ()
 - unlessM :: Monad m => m Bool -> m () -> m ()
 - runReaderT' :: r -> ReaderT r m a -> m a
 - runStateT' :: s -> StateT s m a -> m (a, s)
 - evalStateT' :: Monad m => s -> StateT s m a -> m a
 - execStateT' :: Monad m => s -> StateT s m a -> m s
 - runReader' :: r -> Reader r a -> a
 - runState' :: s -> State s a -> (a, s)
 - evalState' :: s -> State s a -> a
 - execState' :: s -> State s a -> s
 - microseconds :: Int -> Time
 - milliseconds :: Int -> Time
 - seconds :: Int -> Time
 - minutes :: Int -> Time
 - hours :: Int -> Time
 - delayFor :: MonadIO m => Time -> m ()
 - delayMicroseconds :: MonadIO m => Int -> m ()
 - delayMilliseconds :: MonadIO m => Int -> m ()
 - delaySeconds :: MonadIO m => Int -> m ()
 - io :: MonadIO m => IO a -> m a
 - forkever_ :: IO () -> IO ()
 - forkever :: Maybe Int -> IO () -> IO ThreadId
 - forceIO :: NFData a => a -> IO a
 - forceIO_ :: NFData a => a -> IO ()
 - firstSetEnvironmentVariable :: String -> [String] -> IO String
 - firstNonemptyEnvironmentVariable :: String -> [String] -> IO String
 - firstEnvironmentVariableSatisfying :: (String -> Bool) -> String -> [String] -> IO String
 - toLazyByteString :: StrictBytes -> LazyBytes
 
Documentation
A number of microseconds (there are one million microseconds per second). An integral number because it's the smallest resolution for most GHC functions. Int because GHC frequently represents integrals as Ints (for efficiency). 
Has smart constructors for common time units; in particular, for thread delays, and for human-scale durations.
Which also act as self-documenting (psuedo-keyword-)arguments for threadDelay, via delayFor. 
Constructors
| Time | |
Fields  | |
sequence :: (Traversable t, Applicative f) => t (f a) -> f (t a) Source #
(generalization)
 = sequenceA
sequence_ :: (Foldable t, Applicative f) => t (f a) -> f () Source #
(generalization)
  = sequenceA_
(>) :: (a -> b) -> (b -> c) -> a -> c infixr 9 Source #
forwards composition
e.g. "f, then g, then h"
forwards x = x & f > g > h
same precedence/associativity as .
(<) :: (b -> c) -> (a -> b) -> a -> c infixr 9 Source #
backwards composition
e.g. "h, after g, after f"
backwards x = h < g < f $ x
same precedence/associativity as .
greaterThan :: Ord a => a -> a -> Bool infix 4 Source #
same precedence/associativity as "Prelude.>"
(-:) :: a -> b -> (a, b) infix 1 Source #
(-:) = (,)
fake dictionary literal syntax:
[ "a"-: 1 , "b"-: 2 , "c"-: 1+2 ] :: [(String,Integer)]
__BUG__ :: SomeException -> a Source #
nothing :: Applicative m => m () Source #
= pure ()returning :: Applicative m => (a -> b) -> a -> m b Source #
Raise a Function Arrow into a Kleisli Arrow.
a convenience function for composing pure functions between "kleislis" in monadic sequences.
Definition:
= (pure .)returning f ≡ f >>> return returning f ≡ x -> return (f x)
Usage:
readFile "example.txt" >>= returning show >>= forceIO
maybe2bool :: Maybe a -> Bool Source #
maybe2either :: e -> Maybe a -> Either e a Source #
either2maybe :: Either e a -> Maybe a Source #
either2bool :: Either e a -> Bool Source #
maybe2list :: Maybe a -> [a] Source #
list2maybe :: [a] -> Maybe a Source #
nonempty2list :: NonEmpty a -> [a] Source #
unsafeNatural :: Integral i => i -> Natural Source #
unsafeNatural :: Int -> Natural
ratio :: Integral a => a -> a -> Ratio a infixl 7 Source #
an alias, since (%) is prime symbolic real estate. 
ordNub :: Ord a => [a] -> [a] Source #
Remove duplicates (from the given list).
Examples
>>>ordNub "abcab""abc">>>ordNub """"
Definition
ordNub =ordNubByid
Laws
Idempotent (i.e. multiple applications are redundant)
Stable (i.e. preserves the original order)
Performance
Semantically, ordNub should be equivalent to nub.
Operationally, it's much faster for large lists:
nub— only needs anEqconstraint, but takesO(n^2)time complexity.ordNub— needs anOrdconstraint, but only takesO(n log n)time complexity.
Links
- http://github.com/nh2/haskell-ordnub, by Niklas Hambüchen.
 
ordNubBy :: Ord b => (a -> b) -> [a] -> [a] Source #
Selects a key for each element, and takes the nub based on that key.
See ordNub.
nth :: Natural -> [a] -> Maybe a Source #
Safely get the n-th item in the given list.
>>>nth 1 ['a'..'c']Just 'b'>>>nth 1 []Nothing
constructors :: BoundedEnum a => proxy a -> [a] Source #
>>>pBool = Proxy :: Proxy Bool>>>constructors pBool[False,True]
constructors' :: forall a. BoundedEnum a => [a] Source #
like constructors, but with an implicit type parameter.
>>>constructors' == [False,True]True
> :set -XTypeApplications > constructors' @Bool
- False,True
 
runReaderT' :: r -> ReaderT r m a -> m a Source #
evalStateT' :: Monad m => s -> StateT s m a -> m a Source #
execStateT' :: Monad m => s -> StateT s m a -> m s Source #
microseconds :: Int -> Time Source #
milliseconds :: Int -> Time Source #
delayMicroseconds :: MonadIO m => Int -> m () Source #
delayMilliseconds :: MonadIO m => Int -> m () Source #
delaySeconds :: MonadIO m => Int -> m () Source #
firstSetEnvironmentVariable :: String -> [String] -> IO String Source #
Return the value of the first environment variable that's been set, or a default value if all are unset.
Examples:
> firstSetEnvironmentVariable "/usr/run" [ "XDG_RUNTIME_HOME", "TMP" ]
Properties:
firstSetEnvironmentVariable x [] ≡ return x
firstNonemptyEnvironmentVariable :: String -> [String] -> IO String Source #
Return the first nonempty value among the given environment variables, or a default value if all are either unset or set-to-empty.
Examples:
> firstNonemptyEnvironmentVariable "usrrun" [ XDG_RUNTIME_HOME, TMP ]
Properties:
firstNonemptyEnvironmentVariable x [] ≈ return x
Notes:
- on Windows, 
firstNonemptyEnvironmentVariableshould be equivalent tofirstSetEnvironmentVariable.