File: ReifyTypeCUSKs.hs

package info (click to toggle)
haskell-th-desugar 1.15-1
  • links: PTS
  • area: main
  • in suites: forky, sid, trixie
  • size: 476 kB
  • sloc: haskell: 5,446; makefile: 6
file content (121 lines) | stat: -rw-r--r-- 4,128 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
{-# LANGUAGE CPP #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
#if __GLASGOW_HASKELL__ < 806
{-# LANGUAGE TypeInType #-}
#endif
#if __GLASGOW_HASKELL__ >= 809
{-# LANGUAGE CUSKs #-}
#endif
-- This is kept in a separate module from ReifyTypeSigs to isolate the use of
-- the -XCUSKs language extension.
module ReifyTypeCUSKs where

import Data.Kind (Type)
import GHC.Exts (Constraint)
import Language.Haskell.TH.Desugar
import Language.Haskell.TH.Syntax hiding (Type)
import Splices (eqTH)

test_reify_type_cusks, test_reify_type_no_cusks :: [Bool]
(test_reify_type_cusks, test_reify_type_no_cusks) =
  $(do cusk_decls <-
         [d| data A1 (a :: Type)
             type A2 (a :: Type) = (a :: Type)
             type family A3 a
             data family A4 a
             type family A5 (a :: Type) :: Type where
               A5 a = a
             class A6 (a :: Type) where
               type A7 a b

             data A8 (a :: k) :: k -> Type
#if __GLASGOW_HASKELL__ >= 804
             data A9 (a :: j) :: forall k. k -> Type
#endif
#if __GLASGOW_HASKELL__ >= 809
             data A10 (k :: Type) (a :: k)
             data A11 :: forall k -> k -> Type
#endif
           |]

       no_cusk_decls <-
         [d| data B1 a
             type B2 (a :: Type) = a
             type B3 a = (a :: Type)
             type family B4 (a :: Type) where
               B4 a = a
             type family B5 a :: Type where
               B5 a = a
             class B6 a where
               type B7 (a :: Type) (b :: Type) :: Type

             data B8 :: k -> Type
#if __GLASGOW_HASKELL__ >= 804
             data B9 :: forall j. j -> k -> Type
#endif
           |]

       let test_reify_kind :: DsMonad q
                           => String -> (Int, Maybe DKind) -> q Bool
           test_reify_kind prefix (i, expected_kind) = do
             actual_kind <- dsReifyType $ mkName $ prefix ++ show i
             return $ expected_kind `eqTH` actual_kind

           typeKind :: DKind
           typeKind = DConT typeKindName

           type_to_type :: DKind
           type_to_type = DArrowT `DAppT` typeKind `DAppT` typeKind

       cusk_decl_bools <-
         withLocalDeclarations cusk_decls $
         traverse (\(i, k) -> test_reify_kind "A" (i, Just k)) $
           [ (1, type_to_type)
           , (2, type_to_type)
           , (3, type_to_type)
           , (4, type_to_type)
           , (5, type_to_type)
           , (6, DArrowT `DAppT` typeKind `DAppT` DConT ''Constraint)
           , (7, DArrowT `DAppT` typeKind `DAppT` type_to_type)
           ]
           ++
           [ (8, let k = mkName "k" in
                 DForallT (DForallInvis [DPlainTV k SpecifiedSpec]) $
                 DArrowT `DAppT` DVarT k `DAppT`
                   (DArrowT `DAppT` DVarT k `DAppT` typeKind))
           ]
#if __GLASGOW_HASKELL__ >= 804
           ++
           [ (9, let j = mkName "j"
                     k = mkName "k" in
                 DForallT (DForallInvis [DPlainTV j SpecifiedSpec]) $
                 DArrowT `DAppT` DVarT j `DAppT`
                   (DForallT (DForallInvis [DPlainTV k SpecifiedSpec]) $
                    DArrowT `DAppT` DVarT k `DAppT` typeKind))
           ]
#endif
#if __GLASGOW_HASKELL__ >= 809
           ++
           [ (10, let k = mkName "k" in
                  DForallT (DForallVis [DKindedTV k () typeKind]) $
                  DArrowT `DAppT` DVarT k `DAppT` typeKind)
           , (11, let k = mkName "k" in
                  DForallT (DForallVis [DPlainTV k ()]) $
                  DArrowT `DAppT` DVarT k `DAppT` typeKind)
           ]
#endif

       no_cusk_decl_bools <-
         withLocalDeclarations no_cusk_decls $
         traverse (test_reify_kind "B") $
           map (, Nothing) $
                [1..7]
             ++ [8]
#if __GLASGOW_HASKELL__ >= 804
             ++ [9]
#endif
       lift (cusk_decl_bools, no_cusk_decl_bools))