2 {-# LANGUAGE AllowAmbiguousTypes #-}
4 {-# LANGUAGE DataKinds #-}
6 {-# LANGUAGE PatternSynonyms #-}
8 {-# LANGUAGE RankNTypes #-}
10 {-# LANGUAGE TypeFamilyDependencies #-}
12 {-# LANGUAGE UndecidableInstances #-}
14 -- | Combinators in this module conflict with usual ones from the @Prelude@
15 -- hence they are meant to be imported either explicitely or qualified.
16 module Symantic.Syntaxes.Classes where
18 import Control.Category qualified as Cat
19 import Data.Bool (Bool (..))
20 import Data.Char (Char)
21 import Data.Either (Either (..))
23 import Data.Function qualified as Fun
25 import Data.Kind (Constraint)
26 import Data.Maybe (Maybe (..), fromJust)
27 import Data.Proxy (Proxy (..))
28 import Data.Semigroup (Semigroup)
29 import Data.String (String)
30 import Data.Tuple qualified as Tuple
31 import GHC.Generics (Generic)
32 import Numeric.Natural (Natural)
34 import Symantic.Syntaxes.CurryN
35 import Symantic.Syntaxes.Derive
36 import Symantic.Syntaxes.EithersOfTuples
37 import Symantic.Syntaxes.TuplesOfFunctions
40 type Syntax = Semantic -> Constraint
42 -- ** Type family 'Syntaxes'
44 -- | Merge several 'Syntax'es into a single one.
46 -- Useful in 'IfSemantic'.
47 type family Syntaxes (syns :: [Syntax]) (sem :: Semantic) :: Constraint where
49 Syntaxes (syn ': syns) sem = (syn sem, Syntaxes syns sem)
51 -- * Class 'Abstractable'
52 class Unabstractable sem => Abstractable sem where
53 -- | Lambda term abstraction, in HOAS (Higher-Order Abstract Syntax) style.
54 lam :: (sem a -> sem b) -> sem (a -> b)
56 -- | Like 'lam' but whose argument must be used only once,
57 -- hence safe to beta-reduce (inline) without duplicating work.
58 lam1 :: (sem a -> sem b) -> sem (a -> b)
61 lam f = liftDerived (lam (derive Fun.. f Fun.. liftDerived))
62 lam1 f = liftDerived (lam1 (derive Fun.. f Fun.. liftDerived))
63 var = liftDerived1 var
65 FromDerived Abstractable sem =>
70 FromDerived Abstractable sem =>
75 FromDerived1 Abstractable sem =>
79 -- ** Class 'Unabstractable'
80 class Unabstractable sem where
81 -- | Application, aka. unabstract.
82 (.@) :: sem (a -> b) -> sem a -> sem b
85 (.@) = liftDerived2 (.@)
87 FromDerived2 Unabstractable sem =>
92 -- ** Class 'Functionable'
93 class Functionable sem where
94 const :: sem (a -> b -> a)
95 flip :: sem ((a -> b -> c) -> b -> a -> c)
97 (.) :: sem ((b -> c) -> (a -> b) -> a -> c)
99 ($) :: sem ((a -> b) -> a -> b)
101 const = liftDerived const
102 flip = liftDerived flip
104 (.) = liftDerived (.)
105 ($) = liftDerived ($)
107 FromDerived Functionable sem =>
110 FromDerived Functionable sem =>
111 sem ((a -> b -> c) -> b -> a -> c)
113 FromDerived Functionable sem =>
116 FromDerived Functionable sem =>
117 sem ((b -> c) -> (a -> b) -> a -> c)
119 FromDerived Functionable sem =>
120 sem ((a -> b) -> a -> b)
122 -- * Class 'Anythingable'
123 class Anythingable sem where
124 anything :: sem a -> sem a
127 -- * Class 'Bottomable'
128 class Bottomable sem where
131 -- * Class 'Constantable'
132 class Constantable c sem where
133 constant :: c -> sem c
134 constant = liftDerived Fun.. constant
136 FromDerived (Constantable c) sem =>
140 -- * Class 'Eitherable'
141 class Eitherable sem where
142 either :: sem ((l -> a) -> (r -> a) -> Either l r -> a)
143 left :: sem (l -> Either l r)
144 right :: sem (r -> Either l r)
145 either = liftDerived either
146 left = liftDerived left
147 right = liftDerived right
149 FromDerived Eitherable sem =>
150 sem ((l -> a) -> (r -> a) -> Either l r -> a)
152 FromDerived Eitherable sem =>
153 sem (l -> Either l r)
155 FromDerived Eitherable sem =>
156 sem (r -> Either l r)
158 -- * Class 'Equalable'
159 class Equalable sem where
160 equal :: Eq a => sem (a -> a -> Bool)
161 equal = liftDerived equal
163 FromDerived Equalable sem =>
175 (==) x y = equal .@ x .@ y
177 -- * Class 'IfThenElseable'
178 class IfThenElseable sem where
179 ifThenElse :: sem Bool -> sem a -> sem a -> sem a
180 ifThenElse = liftDerived3 ifThenElse
181 default ifThenElse ::
182 FromDerived3 IfThenElseable sem =>
188 -- * Class 'Inferable'
189 class Inferable a sem where
191 default infer :: FromDerived (Inferable a) sem => sem a
192 infer = liftDerived infer
194 unit :: Inferable () sem => sem ()
196 bool :: Inferable Bool sem => sem Bool
198 char :: Inferable Char sem => sem Char
200 int :: Inferable Int sem => sem Int
202 natural :: Inferable Natural sem => sem Natural
204 string :: Inferable String sem => sem String
207 -- * Class 'Listable'
208 class Listable sem where
209 cons :: sem (a -> [a] -> [a])
211 cons = liftDerived cons
212 nil = liftDerived nil
214 FromDerived Listable sem =>
215 sem (a -> [a] -> [a])
217 FromDerived Listable sem =>
220 -- * Class 'Maybeable'
221 class Maybeable sem where
222 nothing :: sem (Maybe a)
223 just :: sem (a -> Maybe a)
224 nothing = liftDerived nothing
225 just = liftDerived just
227 FromDerived Maybeable sem =>
230 FromDerived Maybeable sem =>
233 -- * Class 'IsoFunctor'
234 class IsoFunctor sem where
235 (<%>) :: Iso a b -> sem a -> sem b
237 (<%>) iso = liftDerived1 (iso <%>)
239 FromDerived1 IsoFunctor sem =>
245 data Iso a b = Iso {a2b :: a -> b, b2a :: b -> a}
246 instance Cat.Category Iso where
247 id = Iso Cat.id Cat.id
248 f . g = Iso (a2b f Cat.. a2b g) (b2a g Cat.. b2a f)
250 -- * Class 'ProductFunctor'
252 -- | Beware that this is an @infixr@,
253 -- not @infixl@ like 'Control.Applicative.<*>';
254 -- this is to follow what is expected by 'ADT'.
255 class ProductFunctor sem where
256 (<.>) :: sem a -> sem b -> sem (a, b)
258 (<.>) = liftDerived2 (<.>)
260 FromDerived2 ProductFunctor sem =>
264 (<.) :: sem a -> sem () -> sem a
266 ra <. rb = Iso Tuple.fst (,()) <%> (ra <.> rb)
267 default (<.) :: IsoFunctor sem => sem a -> sem () -> sem a
268 (.>) :: sem () -> sem a -> sem a
270 ra .> rb = Iso Tuple.snd ((),) <%> (ra <.> rb)
271 default (.>) :: IsoFunctor sem => sem () -> sem a -> sem a
273 -- * Class 'SumFunctor'
275 -- | Beware that this is an @infixr@,
276 -- not @infixl@ like 'Control.Applicative.<|>';
277 -- this is to follow what is expected by 'ADT'.
278 class SumFunctor sem where
279 (<+>) :: sem a -> sem b -> sem (Either a b)
281 (<+>) = liftDerived2 (<+>)
283 FromDerived2 SumFunctor sem =>
288 -- | Like @(,)@ but @infixr@.
289 -- Mostly useful for clarity when using 'SumFunctor'.
290 pattern (:!:) :: a -> b -> (a, b)
298 -- * Class 'AlternativeFunctor'
300 -- | Beware that this is an @infixr@,
301 -- not @infixl@ like 'Control.Applicative.<|>';
302 -- this is to follow what is expected by 'ADT'.
303 class AlternativeFunctor sem where
304 (<|>) :: sem a -> sem a -> sem a
306 (<|>) = liftDerived2 (<|>)
308 FromDerived2 AlternativeFunctor sem =>
313 -- * Class 'Dicurryable'
314 class Dicurryable sem where
318 (args -..-> a) -> -- construction
319 (a -> Tuples args) -> -- destruction
322 dicurry args constr destr = liftDerived1 (dicurry args constr destr)
324 FromDerived1 Dicurryable sem =>
328 (a -> Tuples args) ->
338 Tuples args ~ EoT (ADT a) =>
339 (args ~ Args (args -..-> a)) =>
343 construct f = dicurry (Proxy :: Proxy args) f eotOfadt
345 -- * Class 'Dataable'
347 -- | Enable the contruction or deconstruction
348 -- of a any algebraic data type
349 class Dataable sem where
350 data_ :: Generic a => RepOfEoT a => UnToF a => sem (EoT (ADT a)) -> sem a
358 data_ = (<%>) (Iso adtOfeot eotOfadt)
360 -- | Like 'data_' but with the @(a)@ type parameter first
361 -- for convenience when specifying it.
362 dataType :: forall a sem. Dataable sem => Generic a => RepOfEoT a => UnToF a => sem (EoT (ADT a)) -> sem a
365 -- * Class 'IfSemantic'
367 -- | 'IfSemantic' enables to change the 'Syntax' for a specific 'Semantic'.
369 -- Useful when a 'Semantic' does not implement some 'Syntax'es used by other 'Semantic's.
372 (thenSyntaxes :: [Syntax])
373 (elseSyntaxes :: [Syntax])
378 (Syntaxes thenSyntaxes thenSemantic => thenSemantic a) ->
379 (Syntaxes elseSyntaxes elseSemantic => elseSemantic a) ->
384 Syntaxes thenSyntaxes thenSemantic =>
385 IfSemantic thenSyntaxes elseSyntaxes thenSemantic thenSemantic
387 ifSemantic thenSyntax _elseSyntax = thenSyntax
389 Syntaxes elseSyntaxes elseSemantic =>
390 IfSemantic thenSyntaxes elseSyntaxes thenSemantic elseSemantic
392 ifSemantic _thenSyntax elseSyntax = elseSyntax
394 -- * Class 'Monoidable'
406 -- ** Class 'Emptyable'
407 class Emptyable sem where
409 empty = liftDerived empty
411 FromDerived Emptyable sem =>
414 -- ** Class 'Semigroupable'
415 class Semigroupable sem where
416 concat :: Semigroup a => sem (a -> a -> a)
417 concat = liftDerived concat
419 FromDerived Semigroupable sem =>
423 infixr 6 `concat`, <>
431 (<>) x y = concat .@ x .@ y
433 -- ** Class 'Optionable'
434 class Optionable sem where
435 optional :: sem a -> sem (Maybe a)
436 optional = liftDerived1 optional
438 FromDerived1 Optionable sem =>
442 -- * Class 'Repeatable'
443 class Repeatable sem where
444 many0 :: sem a -> sem [a]
445 many1 :: sem a -> sem [a]
446 many0 = liftDerived1 many0
447 many1 = liftDerived1 many1
449 FromDerived1 Repeatable sem =>
453 FromDerived1 Repeatable sem =>
457 -- | Alias to 'many0'.
458 many :: Repeatable sem => sem a -> sem [a]
461 -- | Alias to 'many1'.
462 some :: Repeatable sem => sem a -> sem [a]
465 -- * Class 'Permutable'
466 class Permutable sem where
467 -- Use @TypeFamilyDependencies@ to help type-inference infer @(sem)@.
468 type Permutation (sem :: Semantic) = (r :: Semantic) | r -> sem
469 type Permutation sem = Permutation (Derived sem)
470 permutable :: Permutation sem a -> sem a
471 perm :: sem a -> Permutation sem a
472 noPerm :: Permutation sem ()
473 permWithDefault :: a -> sem a -> Permutation sem a
479 Permutation sem (Maybe a)
480 optionalPerm = permWithDefault Nothing Fun.. (<%>) (Iso Just fromJust)
484 ProductFunctor (Permutation sem) =>
487 Permutation sem (a, b)
488 x <&> y = perm x <.> y
496 ProductFunctor (Permutation sem) =>
499 Permutation sem (Maybe a, b)
500 x <?&> y = optionalPerm x <.> y
502 {-# INLINE (<?&>) #-}
509 ProductFunctor (Permutation sem) =>
512 Permutation sem ([a], b)
513 x <*&> y = permWithDefault [] (many1 x) <.> y
515 {-# INLINE (<*&>) #-}
522 ProductFunctor (Permutation sem) =>
525 Permutation sem ([a], b)
526 x <+&> y = perm (many1 x) <.> y
528 {-# INLINE (<+&>) #-}
530 -- * Class 'Voidable'
531 class Voidable sem where
532 -- | Useful to supply @(a)@ to a @(sem)@ consuming @(a)@,
533 -- for example in the format of a printing interpreter.
534 void :: a -> sem a -> sem ()
535 void = liftDerived1 Fun.. void
537 FromDerived1 Voidable sem =>
542 -- * Class 'Substractable'
543 class Substractable sem where
544 (<->) :: sem a -> sem b -> sem a
546 (<->) = liftDerived2 (<->)
548 FromDerived2 Substractable sem =>