doc: fix minor shortcomings
authorJulien Moutinho <julm+symantic-base@sourcephile.fr>
Sun, 31 Oct 2021 20:11:01 +0000 (21:11 +0100)
committerJulien Moutinho <julm+symantic-base@sourcephile.fr>
Sun, 31 Oct 2021 20:11:01 +0000 (21:11 +0100)
src/Symantic/Class.hs
src/Symantic/Derive.hs
symantic-base.cabal

index 7d5aa776131ab67ec9fa1e4f59f8029c45ab45cd..09d069e6f3ae96dea57b2a91b6dfeb8a25a3b1cc 100644 (file)
@@ -2,6 +2,8 @@
 {-# 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(..))
@@ -25,13 +27,14 @@ import Symantic.ADT
 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
@@ -195,7 +198,7 @@ instance Cat.Category Iso where
 
 -- * 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 <.>
@@ -212,7 +215,7 @@ class ProductFunctor repr where
 
 -- * 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 <+>
@@ -223,7 +226,7 @@ class SumFunctor repr where
 
 -- * 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 <|>
@@ -333,6 +336,14 @@ class Repeatable repr where
     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)@.
@@ -411,8 +422,9 @@ pattern a:!:b <- (a, b)
 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 ::
index b61ff5f971c5ee6cfff59f2873bd8d0cc3d5e18c..87a96b5957ba08f467dfee10a55110e732e16a39 100644 (file)
@@ -11,7 +11,7 @@ import Data.Kind (Type)
 type family Derived (repr :: Type -> Type) :: Type -> Type
 
 -- * Class 'Derivable'
--- | Derive an interpreter to a another interpreter
+-- | Derive an interpreter to another interpreter
 -- determined by the 'Derived' open type family.
 -- This is mostly useful when running the interpreter stack,
 -- but also when going back from an initial encoding to a final one.
index 5cc1f24b4329cf3786879f135d2c001afbc82d3b..5a39cb2dc492182f91f7a884e14e7b3d8bde6245 100644 (file)
@@ -13,7 +13,7 @@ license-file: LICENSES/AGPL-3.0-or-later.txt
 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.
@@ -21,15 +21,15 @@ description:
   * @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@
@@ -39,13 +39,13 @@ description:
     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.