[Haskell-cafe] Statically tracking "validity" - suggestions?

strejon strejony at yahoo.com
Tue Aug 31 06:12:15 EDT 2010



Erik Hesselink wrote:
> 
> If you want to use types instead of modules and hiding as Chris
> suggested, you can use a type index like this:
> 
> {-# LANGUAGE EmptyDataDecls, GADTs, KindSignatures #-}
> data Nothing
> data Just a
> 
> data Subject :: * -> * where
>   NoName :: Subject Nothing
>   Name   :: String -> Subject (Just String)
> 
> data Certificate a = Certificate
>   { subject :: Subject a }
> 
> validate :: Certificate a -> Maybe (Certificate (Just String))
> validate c =
>   case subject c of
>     NoName -> Nothing
>     Name n -> Just c
> 
> A "Certificate (Just String)" now always holds a name, and a
> "Certificate Nothing" doesn't. A "Certificate a" can hold either.
> 
> Erik
> 

Thanks, both of you. The GADT version seems slightly easier
to work with in our case.

-- 
View this message in context: http://old.nabble.com/Statically-tracking-%22validity%22---suggestions--tp29579872p29581285.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.



More information about the Haskell-Cafe mailing list