summaryrefslogtreecommitdiff
path: root/testsuite/tests/simplCore/should_compile/T21391.hs
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/simplCore/should_compile/T21391.hs')
-rw-r--r--testsuite/tests/simplCore/should_compile/T21391.hs25
1 files changed, 25 insertions, 0 deletions
diff --git a/testsuite/tests/simplCore/should_compile/T21391.hs b/testsuite/tests/simplCore/should_compile/T21391.hs
new file mode 100644
index 0000000000..3a974eddb7
--- /dev/null
+++ b/testsuite/tests/simplCore/should_compile/T21391.hs
@@ -0,0 +1,25 @@
+{-# LANGUAGE ConstraintKinds #-}
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE KindSignatures #-}
+{-# LANGUAGE RankNTypes #-}
+module Web.Routing.SafeRouting where
+
+import Control.DeepSeq (NFData (..))
+import Data.Kind (Constraint, Type)
+import Data.Typeable (Typeable)
+
+class FromHttpApiData a where
+
+data PolyMap (c :: Type -> Constraint) (f :: Type -> Type) (a :: Type) where
+ PMNil :: PolyMap c f a
+ PMCons :: (Typeable p, c p) => f (p -> a) -> PolyMap c f a -> PolyMap c f a
+
+rnfHelper :: (forall p. c p => f (p -> a) -> ()) -> PolyMap c f a -> ()
+rnfHelper _ PMNil = ()
+rnfHelper h (PMCons v pm) = h v `seq` rnfHelper h pm
+
+data PathMap x =
+ PathMap [x] (PolyMap FromHttpApiData PathMap x)
+
+instance NFData x => NFData (PathMap x) where
+ rnf (PathMap a b) = rnf a `seq` rnfHelper rnf b