exporting Constructors as pattern-only

All, is there any way in Haskell to export a *data* type so that importing modules can pattern match, but not use the constructors to build anything? My use case is an AST with invariant - I want the convenience of pattern matching with the safety of having to build using functions exported by the model rather than the constructors directly. e.g given data T = T1 Bool | T2 Int | TT T T t1 :: Bool -> T t2 :: Int -> T tt :: T -> T -> T from outside I can write f(T1 False) = tt (t1 True) (t2 42) but not f(T1 False) = TT (T1 True) (T2 42) ? Regards, Andrew Butterfield School of Computer Science & Statistics Trinity College Dublin 2, Ireland

I believe you can use unidirectional pattern synonyms, and only export the patterns, not the constructors. {-# LANGUAGE PatternSynonyms #-} module Tee (T, t1, t2, pattern T1, pattern T2) where data T = MkT1 Bool | MkT2 Int | … pattern T1 a <- MkT1 a pattern T2 a <- MkT2 a … t1 :: Bool -> T t2 :: Int -> T … You can pattern-match on T1 just fine, but if you try to use it as a constructor you’ll get “non-bidirectional pattern synonym ‘T1’ used in an expression”. On Fri, May 19, 2017 at 1:43 AM, Andrew Butterfield < Andrew.Butterfield@scss.tcd.ie> wrote:
All,
is there any way in Haskell to export a *data* type so that importing modules can pattern match, but not use the constructors to build anything?
My use case is an AST with invariant - I want the convenience of pattern matching with the safety of having to build using functions exported by the model rather than the constructors directly.
e.g
given
data T = T1 Bool | T2 Int | TT T T t1 :: Bool -> T t2 :: Int -> T tt :: T -> T -> T
from outside I can write
f(T1 False) = tt (t1 True) (t2 42)
but not
f(T1 False) = TT (T1 True) (T2 42) ?
Regards,
Andrew Butterfield School of Computer Science & Statistics Trinity College Dublin 2, Ireland
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Hi Jon, thanks for that speedy response - looks ideal! I guess though that any tests for module Tee will have to be written inside Tee, rather than in a separate test file - again this is no big deal. Regards, Andrew
On 19 May 2017, at 10:10, Jon Purdy
wrote: I believe you can use unidirectional pattern synonyms, and only export the patterns, not the constructors.
{-# LANGUAGE PatternSynonyms #-} module Tee (T, t1, t2, pattern T1, pattern T2) where
data T = MkT1 Bool | MkT2 Int | … pattern T1 a <- MkT1 a pattern T2 a <- MkT2 a … t1 :: Bool -> T t2 :: Int -> T …
You can pattern-match on T1 just fine, but if you try to use it as a constructor you’ll get “non-bidirectional pattern synonym ‘T1’ used in an expression”.
On Fri, May 19, 2017 at 1:43 AM, Andrew Butterfield
mailto:Andrew.Butterfield@scss.tcd.ie> wrote: All, is there any way in Haskell to export a *data* type so that importing modules can pattern match, but not use the constructors to build anything?
My use case is an AST with invariant - I want the convenience of pattern matching with the safety of having to build using functions exported by the model rather than the constructors directly.
e.g
given
data T = T1 Bool | T2 Int | TT T T t1 :: Bool -> T t2 :: Int -> T tt :: T -> T -> T
from outside I can write
f(T1 False) = tt (t1 True) (t2 42)
but not
f(T1 False) = TT (T1 True) (T2 42) ?
Regards,
Andrew Butterfield School of Computer Science & Statistics Trinity College Dublin 2, Ireland
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
Andrew Butterfield School of Computer Science & Statistics Trinity College Dublin 2, Ireland
participants (2)
-
Andrew Butterfield
-
Jon Purdy