Pattern matching on a private data constructor

左心房为你撑大大i 提交于 2019-12-04 04:06:02

You can define constructor pattern synonyms. This lets you use the same name for smart construction and "dumb" pattern matching.

{-# LANGUAGE PatternSynonyms #-}

module GridAxis (GridAxis, pattern RegularAxis, pattern IrregularAxis) where
import Data.List

data GridAxis = RegularAxis_ (Float, Float) Float -- (min, max) delta
              | IrregularAxis_ [Float]            -- [xs]

-- The line with "<-" defines the matching behavior
-- The line with "=" defines the constructor behavior
pattern RegularAxis minmax delta <- RegularAxis_ minmax delta where
  RegularAxis (a, b) dx = RegularAxis_ (min a b, max a b) (abs dx)

pattern IrregularAxis xs <- IrregularAxis_ xs where
  IrregularAxis xs = IrregularAxis_ (sort xs)

Now you can do:

module Foo
import GridAxis

foo :: GridAxis -> a
foo (RegularAxis (a, b) d) = ...
foo (IrregularAxis xs) = ...

And also use RegularAxis and IrregularAxis as smart constructors.

This looks as a use case for pattern synonyms.

Basically you don't export the real constructor, but only a "smart" one

{-# LANGUAGE PatternSynonyms #-}
module M(T(), SmartCons, smartCons) where

data T = RealCons Int

-- the users will construct T using this
smartCons :: Int -> T
smartCons n = if even n then RealCons n else error "wrong!"

-- ... and destruct T using this
pattern SmartCons n <- RealCons n

Another module importing M can then use

case someTvalue of
   SmartCons n -> use n

and e.g.

let value = smartCons 23 in ...

but can not use the RealCons directly.


If you prefer to stay in basic Haskell, without extensions, you can use a "view type"

module M(T(), smartCons, Tview(..), toView) where
data T = RealCons Int
-- the users will construct T using this
smartCons :: Int -> T
smartCons n = if even n then RealCons n else error "wrong!"

-- ... and destruct T using this
data Tview = Tview Int
toView :: T -> Tview
toView (RealCons n) = Tview n

Here, users have full access to the view type, which can be constructed/destructed freely, but have only a restricted start constructor for the actual type T. Destructing the actual type T is possible by moving to the view type

case toView someTvalue of
  Tview n -> use n

For nested patterns, things become more cumbersome, unless you enable other extensions such as ViewPatterns.

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!