Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Pattern matching on a private data constructor

I'm writing a simple ADT for grid axis. In my application grid may be either regular (with constant step between coordinates), or irregular (otherwise). Of course, the regular grid is just a special case of irregular one, but it may worth to differentiate between them in some situations (for example, to perform some optimizations). So, I declare my ADT as the following:

data GridAxis = RegularAxis (Float, Float) Float -- (min, max) delta
              | IrregularAxis [Float]            -- [xs]

But I don't want user to create malformed axes with max < min or with unordered xs list. So, I add "smarter" construction functions which perform some basic checks:

regularAxis :: (Float, Float) -> Float -> GridAxis
regularAxis (a, b) dx = RegularAxis (min a b, max a b) (abs dx)

irregularAxis :: [Float] -> GridAxis
irregularAxis xs = IrregularAxis (sort xs)

I don't want user to create grids directly, so I don't add GridAxis data constructors into module export list:

module GridAxis (
    GridAxis,
    regularAxis,
    irregularAxis,
    ) where

But it turned out that after having this done I cannot use pattern matching on GridAxis anymore. Trying to use it

import qualified GridAxis as GA

test :: GA.GridAxis -> Bool
test axis = case axis of
              GA.RegularAxis -> True
              GA.IrregularAxis -> False  

gives the following compiler error:

src/Physics/ImplicitEMC.hs:7:15:
    Not in scope: data constructor `GA.RegularAxis'

src/Physics/ImplicitEMC.hs:8:15:
    Not in scope: data constructor `GA.IrregularAxis'

Is there something to work this around?

like image 526
firegurafiku Avatar asked Nov 15 '15 17:11

firegurafiku


2 Answers

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.

like image 100
András Kovács Avatar answered Nov 11 '22 12:11

András Kovács


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.

like image 38
chi Avatar answered Nov 11 '22 13:11

chi