Copyright | (c) 2023 GYELD GMBH |
---|---|
License | Apache 2.0 |
Maintainer | [email protected] |
Stability | develop |
Safe Haskell | Safe-Inferred |
Language | GHC2021 |
GeniusYield.Imports
Contents
Description
Synopsis
- coerce ∷ ∀ {k ∷ RuntimeRep} (a ∷ TYPE k) (b ∷ TYPE k). Coercible a b ⇒ a → b
- guard ∷ Alternative f ⇒ Bool → f ()
- join ∷ Monad m ⇒ m (m a) → m a
- class IsString a where
- fromString ∷ String → a
- liftA2 ∷ Applicative f ⇒ (a → b → c) → f a → f b → f c
- toList ∷ Foldable t ⇒ t a → [a]
- foldl' ∷ Foldable t ⇒ (b → a → b) → b → t a → b
- class Generic a
- data Natural
- type Type = TYPE LiftedRep
- data Constraint
- data CallStack
- forM_ ∷ (Foldable t, Monad m) ⇒ t a → (a → m b) → m ()
- data Set a
- data Map k a
- ap ∷ Monad m ⇒ m (a → b) → m a → m b
- when ∷ Applicative f ⇒ Bool → f () → f ()
- void ∷ Functor f ⇒ f a → f ()
- on ∷ (b → b → c) → (a → b) → a → a → c
- fromMaybe ∷ a → Maybe a → a
- isJust ∷ Maybe a → Bool
- isAlphaNum ∷ Char → Bool
- data Proxy (t ∷ k) = Proxy
- sortBy ∷ (a → a → Ordering) → [a] → [a]
- find ∷ Foldable t ⇒ (a → Bool) → t a → Maybe a
- newtype Const a (b ∷ k) = Const {
- getConst ∷ a
- class (Typeable e, Show e) ⇒ Exception e
- catch ∷ Exception e ⇒ IO a → (e → IO a) → IO a
- throwIO ∷ Exception e ⇒ e → IO a
- newtype Identity a = Identity {
- runIdentity ∷ a
- foldM ∷ (Foldable t, Monad m) ⇒ (b → a → m b) → b → t a → m b
- unless ∷ Applicative f ⇒ Bool → f () → f ()
- absurd ∷ Void → a
- data Void
- data Text
- forM ∷ (Traversable t, Monad m) ⇒ t a → (a → m b) → m (t b)
- class Contravariant (f ∷ Type → Type) where
- class ToJSON a where
- toJSON ∷ a → Value
- toEncoding ∷ a → Encoding
- toJSONList ∷ [a] → Value
- toEncodingList ∷ [a] → Encoding
- class FromJSON a where
- second ∷ Bifunctor p ⇒ (b → c) → p a b → p a c
- bimap ∷ Bifunctor p ⇒ (a → b) → (c → d) → p a c → p b d
- first ∷ Bifunctor p ⇒ (a → b) → p a c → p b c
- class PrintfArg a where
- formatArg ∷ a → FieldFormatter
- parseFormat ∷ a → ModifierParser
- printf ∷ PrintfType r ⇒ String → r
- minimumBy ∷ Foldable t ⇒ (a → a → Ordering) → t a → a
- maximumBy ∷ Foldable t ⇒ (a → a → Ordering) → t a → a
- fromRight ∷ b → Either a b → b
- (>>>) ∷ ∀ {k} cat (a ∷ k) (b ∷ k) (c ∷ k). Category cat ⇒ cat a b → cat b c → cat a c
- data (a ∷ k) :~: (b ∷ k) where
- isHexDigit ∷ Char → Bool
- (&) ∷ a → (a → b) → b
- (<&>) ∷ Functor f ⇒ f a → (a → b) → f b
- type HasCallStack = ?callStack ∷ CallStack
- encodeUtf8 ∷ Text → ByteString
- rightToMaybe ∷ Either a b → Maybe b
- itoList ∷ FoldableWithIndex i f ⇒ f a → [(i, a)]
- ifor_ ∷ (FoldableWithIndex i t, Applicative f) ⇒ t a → (i → a → f b) → f ()
- data Some (tag ∷ k → Type) where
- withSome ∷ Some tag → (∀ (a ∷ k). tag a → b) → b
- mapMaybe ∷ Filterable f ⇒ (a → Maybe b) → f a → f b
- catMaybes ∷ Filterable f ⇒ f (Maybe a) → f a
- wither ∷ (Witherable t, Applicative f) ⇒ (a → f (Maybe b)) → t a → f (t b)
- iwither ∷ (WitherableWithIndex i t, Applicative f) ⇒ (i → a → f (Maybe b)) → t a → f (t b)
- pattern TODO ∷ () ⇒ HasCallStack ⇒ a
- findFirst ∷ Foldable f ⇒ (a → Maybe b) → f a → Maybe b
- decodeUtf8Lenient ∷ ByteString → Text
- lazyDecodeUtf8Lenient ∷ ByteString → Text
- hush ∷ Either e a → Maybe a
- hoistMaybe ∷ Applicative m ⇒ Maybe b → MaybeT m b
Documentation
coerce ∷ ∀ {k ∷ RuntimeRep} (a ∷ TYPE k) (b ∷ TYPE k). Coercible a b ⇒ a → b Source #
The function coerce
allows you to safely convert between values of
types that have the same representation with no run-time overhead. In the
simplest case you can use it instead of a newtype constructor, to go from
the newtype's concrete type to the abstract type. But it also works in
more complicated settings, e.g. converting a list of newtypes to a list of
concrete types.
This function is runtime-representation polymorphic, but the
RuntimeRep
type argument is marked as Inferred
, meaning
that it is not available for visible type application. This means
the typechecker will accept coerce @Int @Age 42
.
guard ∷ Alternative f ⇒ Bool → f () Source #
Conditional failure of Alternative
computations. Defined by
guard True =pure
() guard False =empty
Examples
Common uses of guard
include conditionally signaling an error in
an error monad and conditionally rejecting the current choice in an
Alternative
-based parser.
As an example of signaling an error in the error monad Maybe
,
consider a safe division function safeDiv x y
that returns
Nothing
when the denominator y
is zero and
otherwise. For example:Just
(x `div`
y)
>>>
safeDiv 4 0
Nothing
>>>
safeDiv 4 2
Just 2
A definition of safeDiv
using guards, but not guard
:
safeDiv :: Int -> Int -> Maybe Int safeDiv x y | y /= 0 = Just (x `div` y) | otherwise = Nothing
A definition of safeDiv
using guard
and Monad
do
-notation:
safeDiv :: Int -> Int -> Maybe Int safeDiv x y = do guard (y /= 0) return (x `div` y)
join ∷ Monad m ⇒ m (m a) → m a Source #
The join
function is the conventional monad join operator. It
is used to remove one level of monadic structure, projecting its
bound argument into the outer level.
'
' can be understood as the join
bssdo
expression
do bs <- bss bs
Examples
A common use of join
is to run an IO
computation returned from
an STM
transaction, since STM
transactions
can't perform IO
directly. Recall that
atomically
:: STM a -> IO a
is used to run STM
transactions atomically. So, by
specializing the types of atomically
and join
to
atomically
:: STM (IO b) -> IO (IO b)join
:: IO (IO b) -> IO b
we can compose them as
join
.atomically
:: STM (IO b) -> IO b
class IsString a where Source #
Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).
Methods
fromString ∷ String → a Source #
Instances
liftA2 ∷ Applicative f ⇒ (a → b → c) → f a → f b → f c Source #
Lift a binary function to actions.
Some functors support an implementation of liftA2
that is more
efficient than the default one. In particular, if fmap
is an
expensive operation, it is likely better to use liftA2
than to
fmap
over the structure and then use <*>
.
This became a typeclass method in 4.10.0.0. Prior to that, it was
a function defined in terms of <*>
and fmap
.
Example
>>>
liftA2 (,) (Just 3) (Just 5)
Just (3,5)
toList ∷ Foldable t ⇒ t a → [a] Source #
List of elements of a structure, from left to right. If the entire list is intended to be reduced via a fold, just fold the structure directly bypassing the list.
Examples
Basic usage:
>>>
toList Nothing
[]
>>>
toList (Just 42)
[42]
>>>
toList (Left "foo")
[]
>>>
toList (Node (Leaf 5) 17 (Node Empty 12 (Leaf 8)))
[5,17,12,8]
For lists, toList
is the identity:
>>>
toList [1, 2, 3]
[1,2,3]
Since: base-4.8.0.0
foldl' ∷ Foldable t ⇒ (b → a → b) → b → t a → b Source #
Left-associative fold of a structure but with strict application of the operator.
This ensures that each step of the fold is forced to Weak Head Normal
Form before being applied, avoiding the collection of thunks that would
otherwise occur. This is often what you want to strictly reduce a
finite structure to a single strict result (e.g. sum
).
For a general Foldable
structure this should be semantically identical
to,
foldl' f z =foldl'
f z .toList
Since: base-4.6.0.0
Representable types of kind *
.
This class is derivable in GHC with the DeriveGeneric
flag on.
A Generic
instance must satisfy the following laws:
from
.to
≡id
to
.from
≡id