{-# LANGUAGE PatternSynonyms #-} -- For (:!:)
{-# LANGUAGE TypeFamilyDependencies #-} -- For Permutation
{-# LANGUAGE UndecidableInstances #-} -- For Permutation
+-- | Comibnators in this module conflict with usual ones from the @Prelude@
+-- hence they are meant to be imported either explicitely or qualified.
module Symantic.Class where
import Data.Bool (Bool(..))
import Symantic.CurryN
-- * Type 'ReprKind'
+-- | The kind of @repr@(esentations) throughout this library.
type ReprKind = Type -> Type
-- * Class 'Abstractable'
class Abstractable repr where
-- | Lambda term abstraction, in HOAS (Higher-Order Abstract Syntax) style.
lam :: (repr a -> repr b) -> repr (a->b)
- -- | Like 'lam' but whose argument is used only once,
+ -- | Like 'lam' but whose argument must be used only once,
-- hence safe to beta-reduce (inline) without duplicating work.
lam1 :: (repr a -> repr b) -> repr (a->b)
var :: repr a -> repr a
-- * Class 'ProductFunctor'
-- | Beware that this is an @infixr@,
--- not @infixl@ like to 'Control.Applicative.<*>';
+-- not @infixl@ like 'Control.Applicative.<*>';
-- this is to follow what is expected by 'ADT'.
class ProductFunctor repr where
(<.>) :: repr a -> repr b -> repr (a, b); infixr 4 <.>
-- * Class 'SumFunctor'
-- | Beware that this is an @infixr@,
--- not @infixl@ like to 'Control.Applicative.<|>';
+-- not @infixl@ like 'Control.Applicative.<|>';
-- this is to follow what is expected by 'ADT'.
class SumFunctor repr where
(<+>) :: repr a -> repr b -> repr (Either a b); infixr 3 <+>
-- * Class 'AlternativeFunctor'
-- | Beware that this is an @infixr@,
--- not @infixl@ like to 'Control.Applicative.<|>';
+-- not @infixl@ like 'Control.Applicative.<|>';
-- this is to follow what is expected by 'ADT'.
class AlternativeFunctor repr where
(<|>) :: repr a -> repr a -> repr a; infixr 3 <|>
FromDerived1 Repeatable repr =>
repr a -> repr [a]
+-- | Alias to 'many0'.
+many :: Repeatable repr => repr a -> repr [a]
+many = many0
+
+-- | Alias to 'many1'.
+some :: Repeatable repr => repr a -> repr [a]
+some = many1
+
-- * Class 'Permutable'
class Permutable repr where
-- Use @TypeFamilyDependencies@ to help type-inference infer @(repr)@.
infixr 4 :!:
-- * Class 'Voidable'
--- | FIXME: this class should likely be removed
class Voidable repr where
+ -- | Useful to supply @(a)@ to a @(repr)@ consuming @(a)@,
+ -- for example in the format of a printing interpreter.
void :: a -> repr a -> repr ()
void = liftDerived1 Fun.. void
default void ::
version: 0.3.0.20211007
stability: experimental
category: Data Structures
-synopsis: Basic symantics combinators for Embedded Domain-Specific Languages (EDSL)
+synopsis: Basic symantic combinators for Embedded Domain-Specific Languages (EDSL)
description:
This is a work-in-progress collection of basic tagless-final combinators,
along with some advanced utilities to exploit them.
* @Symantic.Class@
gathers commonly used tagless-final combinators
(the syntax part of symantics).
- * @Symantic.Data@ is an interpreter enabling to pattern-match on combinators,
- while keeping their extensibility.
+ * @Symantic.Data@ interprets combinators as data constructors
+ enabling to pattern-match on combinators while keeping their extensibility.
* @Symantic.Derive@
- enables to give a default value to combinators which avoids boilerplate code
+ to give a default value to combinators which avoids boilerplate code
when implementing combinators for an interpreter is factorizable.
* @Symantic.ObserveSharing@
- enables to observe Haskell @let@ definitions,
- turning infinite values into finite ones,
- which is useful to inspect and optimize recursive grammars for example.
+ interprets combinators to observe @let@ definitions at the host language level (Haskell),
+ effectively turning infinite values into finite ones,
+ which is useful for example to inspect and optimize recursive grammars.
Inspired by Andy Gill's [Type-safe observable sharing in Haskell](https://doi.org/10.1145/1596638.1596653).
For an example, see [symantic-parser](https://hackage.haskell.org/package/symantic-parser).
* @Symantic.Reify@
or functions using such types.
Inspired by Oleg Kiselyov's [TDPE.hs](http://okmij.org/ftp/tagless-final/course/TDPE.hs).
* @Symantic.View@
- is an interpreter enabling to turn combinators into a human-readable string.
+ interprets combinators as a human-readable string.
* @Symantic.ADT@
enables to derive reciprocal functions between
- data-constructors and @Either@s of tuples.
+ algebraic data type constructors and @Either@s of tuples.
* @Symantic.CurryN@
gathers utilities for currying or uncurrying tuples
- of size greater or equal to 2.
+ of size greater or equal to two.
* @Symantic.Fixity@
gathers utilities for parsing or viewing
infix, prefix and postfix combinators.