| Safe Haskell | None |
|---|---|
| Language | GHC2021 |
Rerefined.Predicate.Common
Contents
Description
Handy utilities for defining predicates.
Synopsis
- module Rerefined.Predicate
- proxy# :: forall {k} (a :: k). Proxy# a
- data Builder
- validateFail :: forall {k} (p :: k). (Predicate p, KnownPredicateName p) => Proxy# p -> Builder -> [RefineFailure] -> Maybe RefineFailure
- validateBool :: forall {k} (p :: k). (Predicate p, KnownPredicateName p) => Proxy# p -> Bool -> Builder -> Maybe RefineFailure
Re-exports
module Rerefined.Predicate
proxy# :: forall {k} (a :: k). Proxy# a #
Witness for an unboxed Proxy# value, which has no runtime
representation.
Thin wrapper over Buffer with a handy Semigroup instance.
>>>:set -XOverloadedStrings -XMagicHash>>>fromText "foo" <> fromChar '_' <> fromAddr "bar"#"foo_bar"
Remember: this is a strict builder, so on contrary to Data.Text.Lazy.Builder for optimal performance you should use strict left folds instead of lazy right ones.
Note that (similar to other builders) concatenation of Builders allocates
thunks. This is to a certain extent mitigated by aggressive inlining,
but it is faster to use Buffer directly.
Predicate validation
validateFail :: forall {k} (p :: k). (Predicate p, KnownPredicateName p) => Proxy# p -> Builder -> [RefineFailure] -> Maybe RefineFailure Source #
Shortcut for returning a predicate validation failure.
validateBool :: forall {k} (p :: k). (Predicate p, KnownPredicateName p) => Proxy# p -> Bool -> Builder -> Maybe RefineFailure Source #
Shortcut for simply validating a Bool.