| Safe Haskell | None |
|---|
Language.Google.Search.Simple
Contents
Description
- data Duration
- data Size
- data PrecBuilder = PrecBuilder Int Builder
- parentheses :: Int -> ((PrecBuilder -> Builder) -> Builder) -> PrecBuilder
- class SearchBuilder e where
- searchBuilder :: e -> PrecBuilder
- class SyntaxBuilder f where
- syntaxBuilder :: f PrecBuilder -> PrecBuilder
- class DisjunctF f where
- disjunctF :: e -> e -> f e
- class Disjunct e where
- (\/) :: e -> e -> e
- class ConjunctF f where
- conjunctF :: e -> e -> f e
- class Conjunct e where
- (/\) :: e -> e -> e
- class ComplementF f where
- complementF :: e -> f e
- class Complement e where
- notB :: e -> e
- andB :: Conjunct e => [e] -> e
- orB :: Disjunct e => [e] -> e
- data Term t
- data BooleanF e
- type BooleanM = Free BooleanF
- type Simple = BooleanM (Term Text)
Units
Search expression construction
data PrecBuilder Source
Builder with precedence, though ambiguous associativity.
(But that's okay because Google doesn't mind which way you lean.)
Note that at Google OR binds tighter than conjunction, which is flipped
in contrast to everywhere else. We take the analogous Haskell fixities
when building search expressions:
- 11: atomic tokens or parenthesised expressions
- 10: complementation, search operators (cf. Haskell prefix application)
- 3: disjunction (
ORor|) - 2: conjunction (by juxtaposition)
Constructors
| PrecBuilder Int Builder |
Instances
parentheses :: Int -> ((PrecBuilder -> Builder) -> Builder) -> PrecBuilderSource
Give me the precedence of the piece of syntax you're building, and I'll give you a function that parenthesise any sub-expressions when necessary.
class SearchBuilder e whereSource
Render a search expression using Google search syntax.
Methods
searchBuilder :: e -> PrecBuilderSource
Instances
| SearchBuilder Text | |
| SearchBuilder MailOp | |
| SearchBuilder a => SearchBuilder (Term a) | |
| (Functor f, SearchBuilder a, SyntaxBuilder f) => SearchBuilder (Free f a) |
|
Generalised Boolean operators
class Complement e whereSource
Instances
| ComplementF f => Complement (Free f a) |
Primitive Terms
Fuzzy terms are grouped with parentheses (if necessary), while
Exact terms are always “double-quoted”. The IsString instance
defaults to Fuzzy, so just writing "literal string" ∷
is acceptable.
Term Text
Instances
| Functor Term | |
| SyntaxBuilder Term | |
| Show t => Show (Term t) | |
| IsString t => IsString (Term t) | |
| SearchBuilder a => SearchBuilder (Term a) |
Boolean expressions
The shape of Boolean expressions.