[Haskell-beginners] Structural restrictions in type constructor

Kostiantyn Rybnikov k-bx at k-bx.com
Tue Jun 23 14:33:06 UTC 2015


Imants,

You are right. The problem is not in IO here, it's that if you have access
to data-constructor, you can do things like:

six :: TypeValInt 6
six = TypeValInt 5

Initially, I was making an assumption that you won't be using a
data-constructor. After thinking about it a bit, I should note that my code
isn't much different from just using a "smart constructor" approach, e.g.
hiding a real MyP constructor, and instead providing a function:

mkMyP (a, b) = MyP (a, b) (b, a)

and exporting only this function. This would make sure all your users only
create a valid set of data.


On Tue, Jun 23, 2015 at 5:05 PM, Imants Cekusins <imantc at gmail.com> wrote:

> On 23 June 2015 at 14:54, Kostiantyn Rybnikov <k-bx at k-bx.com> wrote:
> > Hi Matt. I don't know how bad is this, but here's what I came up with.
> ...
>
> this modified for IO version accepts any input, including that which
> should have caused error:
>
> or did I do something wrong?
>
>
> {-# LANGUAGE DataKinds #-}
> {-# LANGUAGE KindSignatures #-}
> {-# LANGUAGE ExistentialQuantification #-}
> {-# LANGUAGE PolyKinds #-}
> {-# LANGUAGE StandaloneDeriving #-}
>
> module PairsMatchedKR where
>
> import GHC.TypeLits
>
> data TypeValInt (n::Nat) = TypeValInt Int
>     deriving (Show)
>
> one :: TypeValInt 1
> one = TypeValInt 1
>
> two :: TypeValInt 2
> two = TypeValInt 2
>
> data MyP a b = MyP (TypeValInt a, TypeValInt b) (TypeValInt b, TypeValInt
> a)
>     deriving (Show)
>
> main :: IO ()
> main = do
>     putStrLn "Hello!"
>     x1 <- getLine
>     x2 <- getLine
>     x3 <- getLine
>     x4 <- getLine
>
>     print (MyP (tvi x1, tvi x2) (tvi x3, tvi x4))
>
> class TypeVal (g :: a -> *)
> instance TypeVal TypeValInt
>
> data MyPGen a b = forall g. (TypeVal g, Show (g a), Show (g b))
>                => MyPGen (g a, g b) (g b, g a)
> deriving instance Show (MyPGen a b)
>
>
> tvi:: String -> TypeValInt (n::Nat)
> tvi = TypeValInt . read
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/beginners/attachments/20150623/31372449/attachment.html>


More information about the Beginners mailing list