Hello,
In Row.hs, `threefreshnames' suffers from a type error due to the monomorphic
restriction. So, I give an explicit type declaration to prevent the type error.
Both ghc4.04 and hugs98 make it to infer types.
Accidentally, I move the declaration of `threefreshnames' to Main.hs.
Then, ghc does not give the type error, but hugs does. I looked into Main.hi.
__interface Main 2 404 where
__export Main threefreshnames;
import NameSupply 4 :: M 1 Name 1 bNS 1 fresh 4 uNS 1;
import Row 1 :: LabelVar 1 zdfNameLabelVar 1;
2 threefreshnames :: Row.LabelVar -> ([[PrelBase.Char]], Row.LabelVar) ;
^^^
The type for threefreshnames seems not to be sufficiently general. Hence,
there seems to be no problem in ghc4.04. Is this behavior intended?
Kwanghoon Choi
P.s. What the `2' does mean?
----------------------------------------------------------
--* Main.hs
----------------------------------------------------------
module Main where
import NameSupply
import Row hiding (threefreshnames)
threefreshnames =
fresh `bNS` (\s1 ->
fresh `bNS` (\s2 ->
fresh `bNS` (\s3 ->
uNS (s1:s2:s3:[]))))
--main = print $ fst $ threefreshnames (initName :: Label)
main = print $ fst $ threefreshnames (initName :: LabelVar)
----------------------------------------------------------
--* Row.hs
----------------------------------------------------------
module Row(Label, LabelVar, Row, threefreshnames) where
import NameSupply
data Row = LRow Label Row | VRow LabelVar
data Label = Label Int
data LabelVar = LabelVar Int
instance Name Label where
toString = \(Label i) -> "l" ++ show i
nextName = \(Label i) -> Label (i+1)
initName = Label 0
instance Name LabelVar where
toString = \(LabelVar i) -> "lv" ++ show i
nextName = \(LabelVar i) -> LabelVar (i+1)
initName = LabelVar 0
threefreshnames :: Name a => M [String] a
threefreshnames =
fresh `bNS` (\s1 ->
fresh `bNS` (\s2 ->
fresh `bNS` (\s3 ->
uNS (s1:s2:s3:[]))))
----------------------------------------------------------
--* NameSupply.hs
----------------------------------------------------------
module NameSupply(M,uNS,bNS,Name(..),fresh) where
-- A Basic Monad for Name Supply
type M a nametype = nametype -> (a, nametype)
uNS :: a -> M a nametype
uNS a = \n -> (a, n)
bNS :: M a nametype -> (a -> M b nametype) -> M b nametype
bNS f g = \n -> case f n of (a,n) -> g a n
-- fresh :: Name a => M String a
-- fresh = \n -> (toString n, nextName n)
fresh n = (toString n, nextName n)
class Name a where
toString :: a -> String
nextName :: a -> a
initName :: a