]> Git — Sourcephile - haskell/symantic.git/blob - symantic-lib/Language/Symantic/Lib/Bounded.hs
Use AllowAmbiguousTypes to avoid Proxy uses.
[haskell/symantic.git] / symantic-lib / Language / Symantic / Lib / Bounded.hs
1 {-# LANGUAGE UndecidableInstances #-}
2 {-# OPTIONS_GHC -fno-warn-orphans #-}
3 -- | Symantic for 'Bounded'.
4 module Language.Symantic.Lib.Bounded where
5
6 import Prelude (Bounded)
7 import Prelude hiding (Bounded(..))
8 import qualified Prelude as Bounded
9
10 import Language.Symantic
11 import Language.Symantic.Lib.Function (a0)
12
13 -- * Class 'Sym_Bounded'
14 type instance Sym (Proxy Bounded) = Sym_Bounded
15 class Sym_Bounded term where
16 minBound :: Bounded a => term a
17 maxBound :: Bounded a => term a
18 default minBound :: Sym_Bounded (UnT term) => Trans term => Bounded a => term a
19 default maxBound :: Sym_Bounded (UnT term) => Trans term => Bounded a => term a
20 minBound = trans minBound
21 maxBound = trans maxBound
22
23 -- Interpreting
24 instance Sym_Bounded Eval where
25 minBound = Eval Bounded.minBound
26 maxBound = Eval Bounded.maxBound
27 instance Sym_Bounded View where
28 minBound = view0 "minBound"
29 maxBound = view0 "maxBound"
30 instance (Sym_Bounded r1, Sym_Bounded r2) => Sym_Bounded (Dup r1 r2) where
31 minBound = dup0 @Sym_Bounded minBound
32 maxBound = dup0 @Sym_Bounded maxBound
33
34 -- Transforming
35 instance (Sym_Lambda term, Sym_Bounded term) => Sym_Bounded (BetaT term)
36
37 -- Typing
38 instance FixityOf Bounded
39 instance ClassInstancesFor Bounded
40 instance TypeInstancesFor Bounded
41
42 -- Compiling
43 instance Gram_Term_AtomsFor src ss g Bounded
44 instance (Source src, Inj_Sym ss Bounded) => ModuleFor src ss Bounded where
45 moduleFor = ["Bounded"] `moduleWhere`
46 [ "minBound" := teBounded_minBound
47 , "maxBound" := teBounded_maxBound
48 ]
49
50 -- ** 'Type's
51 tyBounded :: Source src => Type src vs a -> Type src vs (Bounded a)
52 tyBounded a = tyConstLen @(K Bounded) @Bounded (lenVars a) `tyApp` a
53
54 -- ** 'Term's
55 teBounded_minBound, teBounded_maxBound :: TermDef Bounded '[Proxy a] (Bounded a #> a)
56 teBounded_minBound = Term (tyBounded a0) a0 $ teSym @Bounded $ minBound
57 teBounded_maxBound = Term (tyBounded a0) a0 $ teSym @Bounded $ maxBound