]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Typing/Family.hs
Add Typing.Family and Compiling.MonoFunctor.
[haskell/symantic.git] / Language / Symantic / Typing / Family.hs
1 {-# LANGUAGE DataKinds #-}
2 {-# LANGUAGE PolyKinds #-}
3 {-# LANGUAGE ConstraintKinds #-}
4 {-# LANGUAGE FlexibleContexts #-}
5 {-# LANGUAGE FlexibleInstances #-}
6 {-# LANGUAGE GADTs #-}
7 {-# LANGUAGE MultiParamTypeClasses #-}
8 {-# LANGUAGE ScopedTypeVariables #-}
9 {-# LANGUAGE TypeFamilies #-}
10 {-# LANGUAGE TypeOperators #-}
11 {-# LANGUAGE UndecidableInstances #-}
12 {-# OPTIONS_GHC -fconstraint-solver-iterations=7 #-}
13 module Language.Symantic.Typing.Family where
14
15 import Data.Maybe (fromMaybe)
16 import Data.Proxy
17
18 import Language.Symantic.Typing.Type
19
20 type family Fam fam h0 :: *
21
22 -- * Type 'Proj_Fam'
23 -- | Convenient type synonym wrapping 'Proj_FamR'
24 -- to initiate its recursion.
25 type Proj_Fam cs = Proj_FamR cs cs
26
27 -- | Project the 'Constraint' indexed by the given 'Type'
28 -- onto its proof, captured by 'Con' when it holds.
29 proj_fam
30 :: forall fam cs h. Proj_Fam cs fam
31 => Proxy fam
32 -> Type cs h
33 -> Maybe (Type cs (Fam fam h))
34 proj_fam = proj_famR (Proxy::Proxy cs)
35
36 -- ** Class 'Proj_FamR'
37 -- | Intermediate type class to construct an instance of 'Proj_Fam'
38 -- from many instances of 'Proj_FamC', one for each item of @cs@.
39 --
40 -- * @cs@: starting list of /type constants/.
41 -- * @rs@: remaining list of /type constants/.
42 class Proj_FamR cs rs fam where
43 proj_famR :: Proxy rs -> Proxy fam -> Type cs h -> Maybe (Type cs (Fam fam h))
44 proj_famR _rs _fam _ty = Nothing
45
46 -- | Test whether @c@ handles the work of 'Proj_Fam' or not,
47 -- or recurse on @rs@, preserving the starting list of /type constants/.
48 instance
49 ( Proj_FamC cs fam c
50 , Proj_FamR cs rs fam
51 ) => Proj_FamR cs (c ': rs) fam where
52 proj_famR _rs fam ty =
53 proj_famR (Proxy::Proxy rs) fam ty `fromMaybe`
54 proj_famC (Proxy::Proxy c) fam ty
55 -- | End the recursion.
56 instance Proj_FamR cs '[] fam
57
58 -- ** Class 'Proj_FamC'
59 -- | Handle the work of 'Proj_Fam' for a given /type family/ @fam@ and /type constant/ @c@,
60 -- that is: maybe it handles the given /type family/,
61 -- and if so, maybe the /type family/ has an instance for the given 'Type'.
62 class Proj_FamC cs fam c where
63 proj_famC :: Proxy c -> Proxy fam -> Type cs h -> Maybe (Maybe (Type cs (Fam fam h)))
64 proj_famC _c _fam _ty = Nothing