2 {-# LANGUAGE AllowAmbiguousTypes #-}
 
   4 {-# LANGUAGE DataKinds #-}
 
   6 {-# LANGUAGE PatternSynonyms #-}
 
   8 {-# LANGUAGE RankNTypes #-}
 
  10 {-# LANGUAGE TypeFamilyDependencies #-}
 
  12 {-# LANGUAGE UndecidableInstances #-}
 
  14 -- | This module gathers commonly used tagless-final combinators
 
  15 -- (the syntax part of symantics).
 
  17 -- Note: combinators in this module conflict with usual ones from the @Prelude@
 
  18 -- hence they are meant to be imported either explicitely or qualified.
 
  19 module Symantic.Syntaxes.Classes where
 
  21 import Control.Category qualified as Cat
 
  22 import Data.Bool (Bool (..))
 
  23 import Data.Char (Char)
 
  24 import Data.Either (Either (..))
 
  26 import Data.Function qualified as Fun
 
  28 import Data.Kind (Constraint)
 
  29 import Data.Maybe (Maybe (..), fromJust)
 
  30 import Data.Proxy (Proxy (..))
 
  31 import Data.Semigroup (Semigroup)
 
  32 import Data.String (String)
 
  33 import Data.Tuple qualified as Tuple
 
  34 import GHC.Generics (Generic)
 
  35 import Numeric.Natural (Natural)
 
  37 import Symantic.Syntaxes.CurryN
 
  38 import Symantic.Syntaxes.Derive
 
  39 import Symantic.Syntaxes.EithersOfTuples
 
  42 type Syntax = Semantic -> Constraint
 
  44 -- ** Type family 'Syntaxes'
 
  46 -- | Merge several 'Syntax'es into a single one.
 
  48 -- Useful in 'IfSemantic' or 'All'.
 
  49 type family Syntaxes (syns :: [Syntax]) (sem :: Semantic) :: Constraint where
 
  50   Syntaxes '[] sem = (() :: Constraint)
 
  51   Syntaxes (syn ': syns) sem = ((syn sem, Syntaxes syns sem) :: Constraint)
 
  53 -- * Class 'Abstractable'
 
  54 class Abstractable sem where
 
  55   -- | Lambda term abstraction, in HOAS (Higher-Order Abstract Syntax) style.
 
  56   lam :: (sem a -> sem b) -> sem (a -> b)
 
  57   lam f = liftDerived (lam (derive Fun.. f Fun.. liftDerived))
 
  59     FromDerived Abstractable sem =>
 
  64 -- ** Class 'Abstractable1'
 
  65 class Abstractable1 sem where
 
  66   -- | Like 'lam' but whose argument must be used only once,
 
  67   -- hence safe to beta-reduce (inline) without duplicating work.
 
  68   lam1 :: (sem a -> sem b) -> sem (a -> b)
 
  69   lam1 f = liftDerived (lam1 (derive Fun.. f Fun.. liftDerived))
 
  71     FromDerived Abstractable1 sem =>
 
  77 class Varable sem where
 
  78   -- | Mark the use of a variable.
 
  80   var = liftDerived1 var
 
  81   default var :: FromDerived1 Varable sem => sem a -> sem a
 
  83 -- ** Class 'Instantiable'
 
  84 class Instantiable sem where
 
  86   (.@) :: sem (a -> b) -> sem a -> sem b
 
  89   (.@) = liftDerived2 (.@)
 
  91     FromDerived2 Instantiable sem =>
 
  96 -- ** Class 'Unabstractable'
 
  97 -- | All operations in lambda calculus can be encoded
 
  98 -- via abstraction elimination into the SK calculus
 
  99 -- as binary trees whose leaves are one
 
 100 -- of the three symbols S ('ap') and K ('const').
 
 101 class Unabstractable sem where
 
 103   ap :: sem ((a -> b -> c) -> (a -> b) -> a -> c)
 
 105   const :: sem (a -> b -> a)
 
 109   (.) :: sem ((b -> c) -> (a -> b) -> a -> c)
 
 112   flip :: sem ((a -> b -> c) -> b -> a -> c)
 
 113   ($) :: sem ((a -> b) -> a -> b)
 
 117   const = liftDerived const
 
 119   (.) = liftDerived (.)
 
 120   flip = liftDerived flip
 
 121   ($) = liftDerived ($)
 
 124     FromDerived Unabstractable sem =>
 
 125     sem ((a -> b -> c) -> (a -> b) -> a -> c)
 
 127     FromDerived Unabstractable sem =>
 
 130     FromDerived Unabstractable sem =>
 
 133     FromDerived Unabstractable sem =>
 
 134     sem ((b -> c) -> (a -> b) -> a -> c)
 
 136     FromDerived Unabstractable sem =>
 
 137     sem ((a -> b -> c) -> b -> a -> c)
 
 139     FromDerived Unabstractable sem =>
 
 140     sem ((a -> b) -> a -> b)
 
 142 -- * Class 'Anythingable'
 
 143 class Anythingable sem where
 
 144   anything :: sem a -> sem a
 
 147 -- * Class 'Bottomable'
 
 148 class Bottomable sem where
 
 151 -- * Class 'Constantable'
 
 152 class Constantable c sem where
 
 153   constant :: c -> sem c
 
 154   constant = liftDerived Fun.. constant
 
 156     FromDerived (Constantable c) sem =>
 
 160 -- * Class 'Eitherable'
 
 161 class Eitherable sem where
 
 162   either :: sem ((l -> a) -> (r -> a) -> Either l r -> a)
 
 163   left :: sem (l -> Either l r)
 
 164   right :: sem (r -> Either l r)
 
 165   either = liftDerived either
 
 166   left = liftDerived left
 
 167   right = liftDerived right
 
 169     FromDerived Eitherable sem =>
 
 170     sem ((l -> a) -> (r -> a) -> Either l r -> a)
 
 172     FromDerived Eitherable sem =>
 
 173     sem (l -> Either l r)
 
 175     FromDerived Eitherable sem =>
 
 176     sem (r -> Either l r)
 
 178 -- * Class 'Equalable'
 
 179 class Equalable sem where
 
 180   equal :: Eq a => sem (a -> a -> Bool)
 
 181   equal = liftDerived equal
 
 183     FromDerived Equalable sem =>
 
 195 (==) x y = equal .@ x .@ y
 
 197 -- * Class 'IfThenElseable'
 
 198 class IfThenElseable sem where
 
 199   ifThenElse :: sem Bool -> sem a -> sem a -> sem a
 
 200   ifThenElse = liftDerived3 ifThenElse
 
 201   default ifThenElse ::
 
 202     FromDerived3 IfThenElseable sem =>
 
 208 -- * Class 'Inferable'
 
 209 class Inferable a sem where
 
 211   default infer :: FromDerived (Inferable a) sem => sem a
 
 212   infer = liftDerived infer
 
 214 unit :: Inferable () sem => sem ()
 
 216 bool :: Inferable Bool sem => sem Bool
 
 218 char :: Inferable Char sem => sem Char
 
 220 int :: Inferable Int sem => sem Int
 
 222 natural :: Inferable Natural sem => sem Natural
 
 224 string :: Inferable String sem => sem String
 
 227 -- * Class 'Listable'
 
 228 class Listable sem where
 
 229   cons :: sem (a -> [a] -> [a])
 
 231   cons = liftDerived cons
 
 232   nil = liftDerived nil
 
 234     FromDerived Listable sem =>
 
 235     sem (a -> [a] -> [a])
 
 237     FromDerived Listable sem =>
 
 240 -- * Class 'Maybeable'
 
 241 class Maybeable sem where
 
 242   nothing :: sem (Maybe a)
 
 243   just :: sem (a -> Maybe a)
 
 244   nothing = liftDerived nothing
 
 245   just = liftDerived just
 
 247     FromDerived Maybeable sem =>
 
 250     FromDerived Maybeable sem =>
 
 253 -- * Class 'IsoFunctor'
 
 254 class IsoFunctor sem where
 
 255   (<%>) :: Iso a b -> sem a -> sem b
 
 257   (<%>) iso = liftDerived1 (iso <%>)
 
 259     FromDerived1 IsoFunctor sem =>
 
 265 data Iso a b = Iso {a2b :: a -> b, b2a :: b -> a}
 
 266 instance Cat.Category Iso where
 
 267   id = Iso Cat.id Cat.id
 
 268   f . g = Iso (a2b f Cat.. a2b g) (b2a g Cat.. b2a f)
 
 270 -- * Class 'ProductFunctor'
 
 272 -- | Beware that this is an @infixr@,
 
 273 -- not @infixl@ like 'Control.Applicative.<*>';
 
 274 -- this is to follow what is expected by 'ADT'.
 
 275 class ProductFunctor sem where
 
 276   (<.>) :: sem a -> sem b -> sem (a, b)
 
 278   (<.>) = liftDerived2 (<.>)
 
 280     FromDerived2 ProductFunctor sem =>
 
 284   (<.) :: sem a -> sem () -> sem a
 
 286   ra <. rb = Iso Tuple.fst (,()) <%> (ra <.> rb)
 
 287   default (<.) :: IsoFunctor sem => sem a -> sem () -> sem a
 
 288   (.>) :: sem () -> sem a -> sem a
 
 290   ra .> rb = Iso Tuple.snd ((),) <%> (ra <.> rb)
 
 291   default (.>) :: IsoFunctor sem => sem () -> sem a -> sem a
 
 293 -- * Class 'SumFunctor'
 
 295 -- | Beware that this is an @infixr@,
 
 296 -- not @infixl@ like 'Control.Applicative.<|>';
 
 297 -- this is to follow what is expected by 'ADT'.
 
 298 class SumFunctor sem where
 
 299   (<+>) :: sem a -> sem b -> sem (Either a b)
 
 301   (<+>) = liftDerived2 (<+>)
 
 303     FromDerived2 SumFunctor sem =>
 
 308 -- | Like @(,)@ but @infixr@.
 
 309 -- Mostly useful for clarity when using 'SumFunctor'.
 
 310 pattern (:!:) :: a -> b -> (a, b)
 
 317 {-# COMPLETE (:!:) #-}
 
 319 -- * Class 'AlternativeFunctor'
 
 321 -- | Beware that this is an @infixr@,
 
 322 -- not @infixl@ like 'Control.Applicative.<|>';
 
 323 -- this is to follow what is expected by 'ADT'.
 
 324 class AlternativeFunctor sem where
 
 325   (<|>) :: sem a -> sem a -> sem a
 
 327   (<|>) = liftDerived2 (<|>)
 
 329     FromDerived2 AlternativeFunctor sem =>
 
 334 -- * Class 'Dicurryable'
 
 335 class Dicurryable sem where
 
 339     (args -..-> a) -> -- construction
 
 340     (a -> Tuples args) -> -- destruction
 
 343   dicurry args constr destr = liftDerived1 (dicurry args constr destr)
 
 345     FromDerived1 Dicurryable sem =>
 
 349     (a -> Tuples args) ->
 
 359   Tuples args ~ EoT (ADT a) =>
 
 360   (args ~ Args (args -..-> a)) =>
 
 364 construct f = dicurry (Proxy :: Proxy args) f eotOfadt
 
 366 -- * Class 'Dataable'
 
 368 -- | Enable the contruction or deconstruction
 
 369 -- of an 'ADT' (algebraic data type).
 
 370 class Dataable a sem where
 
 371   dataType :: sem (EoT (ADT a)) -> sem a
 
 379   dataType = (<%>) (Iso adtOfeot eotOfadt)
 
 381 -- * Class 'IfSemantic'
 
 383 -- | 'IfSemantic' enables to change the 'Syntax' for a specific 'Semantic'.
 
 385 -- Useful when a 'Semantic' does not implement some 'Syntax'es used by other 'Semantic's.
 
 388     (thenSyntaxes :: [Syntax])
 
 389     (elseSyntaxes :: [Syntax])
 
 394     (Syntaxes thenSyntaxes thenSemantic => thenSemantic a) ->
 
 395     (Syntaxes elseSyntaxes elseSemantic => elseSemantic a) ->
 
 400   Syntaxes thenSyntaxes thenSemantic =>
 
 401   IfSemantic thenSyntaxes elseSyntaxes thenSemantic thenSemantic
 
 403   ifSemantic thenSyntax _elseSyntax = thenSyntax
 
 405   Syntaxes elseSyntaxes elseSemantic =>
 
 406   IfSemantic thenSyntaxes elseSyntaxes thenSemantic elseSemantic
 
 408   ifSemantic _thenSyntax elseSyntax = elseSyntax
 
 410 -- * Class 'Monoidable'
 
 422 -- ** Class 'Emptyable'
 
 423 class Emptyable sem where
 
 425   empty = liftDerived empty
 
 427     FromDerived Emptyable sem =>
 
 430 -- ** Class 'Semigroupable'
 
 431 class Semigroupable sem where
 
 432   concat :: Semigroup a => sem (a -> a -> a)
 
 433   concat = liftDerived concat
 
 435     FromDerived Semigroupable sem =>
 
 439 infixr 6 `concat`, <>
 
 447 (<>) x y = concat .@ x .@ y
 
 449 -- ** Class 'Optionable'
 
 450 class Optionable sem where
 
 451   optional :: sem a -> sem (Maybe a)
 
 452   optional = liftDerived1 optional
 
 454     FromDerived1 Optionable sem =>
 
 458 -- * Class 'Repeatable'
 
 459 class Repeatable sem where
 
 460   many0 :: sem a -> sem [a]
 
 461   many1 :: sem a -> sem [a]
 
 462   many0 = liftDerived1 many0
 
 463   many1 = liftDerived1 many1
 
 465     FromDerived1 Repeatable sem =>
 
 469     FromDerived1 Repeatable sem =>
 
 473 -- | Alias to 'many0'.
 
 474 many :: Repeatable sem => sem a -> sem [a]
 
 477 -- | Alias to 'many1'.
 
 478 some :: Repeatable sem => sem a -> sem [a]
 
 481 -- * Class 'Permutable'
 
 482 class Permutable sem where
 
 483   -- Use @TypeFamilyDependencies@ to help type-inference infer @(sem)@.
 
 484   type Permutation (sem :: Semantic) = (r :: Semantic) | r -> sem
 
 485   type Permutation sem = Permutation (Derived sem)
 
 486   permutable :: Permutation sem a -> sem a
 
 487   perm :: sem a -> Permutation sem a
 
 488   noPerm :: Permutation sem ()
 
 489   permWithDefault :: a -> sem a -> Permutation sem a
 
 495     Permutation sem (Maybe a)
 
 496   optionalPerm = permWithDefault Nothing Fun.. (<%>) (Iso Just fromJust)
 
 500   ProductFunctor (Permutation sem) =>
 
 503   Permutation sem (a, b)
 
 504 x <&> y = perm x <.> y
 
 512   ProductFunctor (Permutation sem) =>
 
 515   Permutation sem (Maybe a, b)
 
 516 x <?&> y = optionalPerm x <.> y
 
 518 {-# INLINE (<?&>) #-}
 
 525   ProductFunctor (Permutation sem) =>
 
 528   Permutation sem ([a], b)
 
 529 x <*&> y = permWithDefault [] (many1 x) <.> y
 
 531 {-# INLINE (<*&>) #-}
 
 538   ProductFunctor (Permutation sem) =>
 
 541   Permutation sem ([a], b)
 
 542 x <+&> y = perm (many1 x) <.> y
 
 544 {-# INLINE (<+&>) #-}
 
 546 -- * Class 'Voidable'
 
 547 class Voidable sem where
 
 548   -- | Useful to supply @(a)@ to a @(sem)@ consuming @(a)@,
 
 549   -- for example in the format of a printing interpreter.
 
 550   void :: a -> sem a -> sem ()
 
 551   void = liftDerived1 Fun.. void
 
 553     FromDerived1 Voidable sem =>
 
 558 -- * Class 'Substractable'
 
 559 class Substractable sem where
 
 560   (<->) :: sem a -> sem b -> sem a
 
 562   (<->) = liftDerived2 (<->)
 
 564     FromDerived2 Substractable sem =>