Safe Haskell | Safe-Inferred |
---|---|
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
- class IsString a
- validateFail :: forall p. (Predicate p, KnownPredicateName p) => Proxy# p -> Builder -> [RefineFailure] -> Maybe RefineFailure
- validateBool :: forall p. (Predicate p, KnownPredicateName p) => Proxy# p -> Builder -> Bool -> Maybe RefineFailure
- type KnownPredicateName p = KnownSymbol (PredicateName 0 p)
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 Builder
s allocates
thunks. This is to a certain extent mitigated by aggressive inlining,
but it is faster to use Buffer
directly.
IsString
is used in combination with the -XOverloadedStrings
language extension to convert the literals to different string types.
For example, if you use the text package, you can say
{-# LANGUAGE OverloadedStrings #-} myText = "hello world" :: Text
Internally, the extension will convert this to the equivalent of
myText = fromString @Text ("hello world" :: String)
Note: You can use fromString
in normal code as well,
but the usual performance/memory efficiency problems with String
apply.
Minimal complete definition
Instances
IsString ByteString | Beware: |
Defined in Data.ByteString.Internal.Type Methods fromString :: String -> ByteString # | |
IsString ByteString | Beware: |
Defined in Data.ByteString.Lazy.Internal Methods fromString :: String -> ByteString # | |
IsString ShortByteString | Beware: |
Defined in Data.ByteString.Short.Internal Methods fromString :: String -> ShortByteString # | |
IsString Doc | |
Defined in Text.PrettyPrint.HughesPJ Methods fromString :: String -> Doc # | |
IsString Builder | |
Defined in Data.Text.Builder.Linear Methods fromString :: String -> Builder # | |
IsString a => IsString (Identity a) | Since: base-4.9.0.0 |
Defined in Data.String Methods fromString :: String -> Identity a # | |
a ~ Char => IsString (Seq a) | Since: containers-0.5.7 |
Defined in Data.Sequence.Internal Methods fromString :: String -> Seq a # | |
(IsString a, Hashable a) => IsString (Hashed a) | |
Defined in Data.Hashable.Class Methods fromString :: String -> Hashed a # | |
IsString (Doc a) | |
Defined in Text.PrettyPrint.Annotated.HughesPJ Methods fromString :: String -> Doc a # | |
a ~ Char => IsString [a] |
Since: base-2.1 |
Defined in Data.String Methods fromString :: String -> [a] # | |
IsString a => IsString (Const a b) | Since: base-4.9.0.0 |
Defined in Data.String Methods fromString :: String -> Const a b # |
Predicate validation
validateFail :: forall p. (Predicate p, KnownPredicateName p) => Proxy# p -> Builder -> [RefineFailure] -> Maybe RefineFailure Source #
Shortcut for returning a predicate validation failure.
validateBool :: forall p. (Predicate p, KnownPredicateName p) => Proxy# p -> Builder -> Bool -> Maybe RefineFailure Source #
Shortcut for simply validating a Bool
.
type KnownPredicateName p = KnownSymbol (PredicateName 0 p) Source #