Generating a list of random numbers with foldM - haskell

I want to generate a list of random numbers, where the range of each random number is determined by elements of a provided list. I thought I had something that made sense, but I get errors I don't understand :(
Here's what I have:
useRNG nums min = do
generator <- get
let (val, generator') = randomR (min, 51) generator
put generator'
return $ val : nums
foldM useRNG [] [0 .. 50]
Can anyone help me out?

The problem is that useRNG can generate all kinds of numbers (any instance of Random), and work in all kinds of monads (any state monad whose state is an instance of RandomGen), as can be seen from its inferred type signature:
GHCi> :t useRNG
useRNG
:: (MonadState s m, RandomGen s, Random a, Num a) =>
[a] -> a -> m [a]
...but when you use it, you haven't specified which concrete types you actually want.
If you disambiguate with a type signature:
test :: State StdGen [Int]
test = foldM useRNG [] [0 .. 50]
then it works fine. You could also accomplish this by putting a type signature on useRNG:
useRNG :: [Int] -> Int -> State StdGen [Int]
Now, you might be thinking: if useRNG works fine with all these types, why can't test too? The answer is the monomorphism restriction, which is fairly arcane and not well-liked by many Haskell users. You can avoid it by either putting
{-# LANGUAGE NoMonomorphismRestriction #-}
at the top of your file, or giving test an explicit type signature:
test :: (RandomGen g, Random a, Num a, Enum a, MonadState g m) => m [a]
You can find out the correct type signature with GHCi:
GHCi> :t foldM useRNG [] [0 .. 50]
foldM useRNG [] [0 .. 50]
:: (MonadState s m, RandomGen s, Random b, Num b, Enum b) => m [b]
(I wrote the explicit type signature before checking with GHCi, which is why mine is slightly different.)
However, this type signature is a little too polymorphic for practical uses — you'll basically be putting the ambiguity off until you actually use the result — so I'd suggest specifying it more concretely in this instance. You could, for instance, keep test generic over the type of random number without the needless polymorphism over the state monad and generator type:
test :: (Random a, Num a, Enum a) => State StdGen [a]
You might also want to consider using MonadRandom, which wraps all the standard random number generation facilities in a state monad-based interface so you don't have to :)

Related

Haskell type checking and determinism

According to the Haskell 2010 language report, its type checker is based on Hindley-Milner. So consider a function f of this type,
f :: forall a. [a] -> Int
It could be the length function for instance. According to Hindley-Milner, f [] type checks to Int. We can prove this by instantiating the type of f to [Int] -> Int, and the type of [] to [Int], then conclude that the application ([Int] -> Int) [Int] is of type Int.
In this proof, I chose to instantiate types forall a. [a] -> Int and forall a. [a] by substituting Int to a. I can substitute Bool instead, the proof works too. Isn't it strange in Hindley-Milner that we can apply a polymorphic type to another, without specifying which instances we use ?
More specifically, what in Haskell prevents me from using the type a in the implementation of f ? I could imagine that f is a function that equals 18 on any [Bool], and equals the usual length function on all other types of lists. In this case, would f [] be 18 or 0 ? The Haskell report says "the kernel is not formally specified", so it's hard to tell.
During type inference, such type variables can indeed instantiated to any type. This may be seen as a highly non deterministic step.
GHC, for what it is worth, uses the internal Any type in such cases. For instance, compiling
{-# NOINLINE myLength #-}
myLength :: [a] -> Int
myLength = length
test :: Int
test = myLength []
results in the following Core:
-- RHS size: {terms: 3, types: 4, coercions: 0}
myLength [InlPrag=NOINLINE] :: forall a_aw2. [a_aw2] -> Int
[GblId, Str=DmdType]
myLength =
\ (# a_aP5) -> length # [] Data.Foldable.$fFoldable[] # a_aP5
-- RHS size: {terms: 2, types: 6, coercions: 0}
test :: Int
[GblId, Str=DmdType]
test = myLength # GHC.Prim.Any (GHC.Types.[] # GHC.Prim.Any)
where GHC.Prim.Any occurs in the last line.
Now, is that really not deterministic? Well, it does involve a kind of non deterministic step "in the middle" of the algorithm, but the final resulting (most general) type is Int, and deterministically so. It does not matter what type we choose for a, we always get type Int at the end.
Of course, getting the same type is not enough: we also want to get the same Int value. I conjecture that it can be proven that, given
f :: forall a. T a
g :: forall a. T a -> U
then
g # V (f # V) :: U
is the same value whatever type V is. This should be a consequence of parametricity applied to those polymorphic types.
To follow-up on Chi's answer, here is the proof that f [] cannot depend on the type instances of f and []. According to Theorems for free (the last article here),
for any types a,a' and any function g :: a -> a', then
f_a = f_a' . map g
where f_a is the instantiation of f on type a, for example in Haskell
f_Bool :: [Bool] -> Int
f_Bool = f
Then if you evaluate the previous equality on []_a, it yields f_a []_a = f_a' []_a'. In the case of the original question, f_Int []_Int = f_Bool []_Bool.
Some references for parametricity in Haskell would be useful too, because Haskell looks stronger than the polymorphic lambda calculus described in Walder's paper. In particular, this wiki page says parametricity can be broken in Haskell by using the seq function.
The wiki page also says that my type-depending function exists (in other languages than Haskell), it is called ad-hoc polymorphism.

Different types in sum function

I'm new to Haskell so this could be a stupid question. I'm reading a book where it says :type sum is supposed to show sum :: (Num a) => [a] -> a. Instead of that the message is sum :: (Num a, Foldable t) => t a -> a. As I've seen in https://www.haskell.org/hoogle/?hoogle=Sum this difference is due to -I think- the existence of two different sum functions. Maybe it's something like polymorphism in Java, I'm just starting and I have no idea about how Haskell works.
So my questions are: how could I use the sum function which type is sum :: (Num a) => [a] -> a instead of the other one? Could you explain me what's going on here?
As I've seen in https://www.haskell.org/hoogle/?hoogle=Sum this difference is due to -I think- the existence of two different sum functions. Maybe it's something like polymorphism in Java
It is, indeed, polymorphism, though not in this way (see the P.S. at the end of this answer). Note that...
sum :: (Num a) => [a] -> a
... is already polymorphic in the type of the numbers being summed, so it would work with, for instance, lists of Integer and lists of Double. The difference between that and...
sum :: (Num a, Foldable t) => t a -> a
... is that this sum is also polymorphic in the type of the container:
GHCi> -- +t makes GHCi print the types automatically.
GHCi> :set +t
GHCi> sum [1 :: Integer, 2, 3]
6
it :: Integer
GHCi> sum [1 :: Double, 2, 3]
6.0
it :: Double
GHCi> import qualified Data.Set as S
GHCi> :t S.fromList
S.fromList :: Ord a => [a] -> S.Set a
GHCi> sum (S.fromList [1 :: Double, 2, 3])
6.0
it :: Double
For a container type to be used with sum, it has to have an instance of the Foldable class, which covers functions that, like sum, might be expressed as flattening the container into a list and then folding it in some way.
P.S.: Your book says something different than what you have seen because until quite recently the sum function in the Prelude used to have the less general, list-specific type, and your book predates the change. Having two different functions called sum, even if one is strictly more general than the other, would lead to a name clash (it was for a similar reason that I imported the Data.Set module qualified in the example above -- it is a good idea to do so because it defines a few functions such as map that clash with Prelude functions, and qualifying them with, say, S.map avoids any issues).

Using makeLenses, class constraints and type synonyms together

I'm quite new to Haskell and want to use makeLenses from Control.Lens and class constraints together with type synonyms to make my functions types more compact (readable?).
I've tried to come up with a minimal dummy example to demonstrate what I want to achieve and the example serves no other purpose than this.
At the end of this post I've added an example closer to my original problem if you are interested in the context.
Minimal example
As an example, say I define the following data type:
data State a = State { _a :: a
} deriving Show
, for which I also make lenses:
makeLenses ''State
In order to enforce a class constraint on the type parameter a used by the type constructor State I use a smart constructor:
mkState :: (Num a) => a -> State a
mkState n = State {_a = n}
Next, say I have a number of functions with type signatures similar to this:
doStuff :: Num a => State a -> State a
doStuff s = s & a %~ (*2)
This all works as intended, for example:
test = doStuff . mkState $ 5.5 -- results in State {_a = 11.0}
Problem
I've tried to use the following type synonym:
type S = (Num n) => State n -- Requires the RankNTypes extensions
, together with:
{-# LANGUAGE RankNTypes #-}
, in an attempt to simplify the type signature of doStuff:
doStuff :: S -> S
, but this gives the following error:
Couldn't match type `State a0' with `forall n. Num n => State n'
Expected type: a0 -> S
Actual type: a0 -> State a0
In the second argument of `(.)', namely `mkState'
In the expression: doStuff . mkState
In the expression: doStuff . mkState $ 5.5
Failed, modules loaded: none.
Question
My current knowledge of Haskell is not sufficient to understand what causes the above error. I hope someone can explain what causes the error and/or suggest other ways to construct the type synonym or why such a type synonym is not possible.
Background
My original problem looks closer to this:
data State r = State { _time :: Int
, _ready :: r
} deriving Show
makeLenses ''State
data Task = Task { ... }
Here I want to enforce the type of _ready being an instance of the Queue class using the following smart constructor:
mkState :: (Queue q) => Int -> q Task -> State (q Task)
mkState t q = State { _time = t
, _ready = q
}
I also have a number of functions with type signatures similar to this:
updateState :: Queue q => State (q Task) -> Task -> State (q Task)
updateState s x = s & ready %~ (enqueue x) & time %~ (+1)
I would like to use a type synonym S to be able to rewrite the type of such functions as:
updateState :: S -> Task -> S
, but as with the first minimal example I don't know how to define the type synonym S or whether it is possible at all.
Maybe there is no real benefit in trying to simplify the type signatures?
Related reading
I've read the following related questions on SO:
Class constraints for data records
Are type synonyms with typeclass constraints possible?
This might also be related but given my current understanding of Haskell I cannot really understand all of it:
Unifying associated type synonyms with class constraints
Follow-up
It's been a while since I've had the opportunity to do some Haskell. Thanks to #bheklilr I've now managed to introduce a type synonym only to hit the next type error I'm still not able to understand. I've posted the following follow-up question Type synonym causes type error regarding the new type error.
You see that error in particular because of the combination of the . operator and your use of RankNTypes. If you change it from
test = doStuff . mkState $ 5.5
to
test = doStuff $ mkState 5.5
or even
test = doStuff (mkState 5.5)
it will compile. Why is this? Look at the types:
doStuff :: forall n. Num n => State n -> State n
mkState :: Num n => n -> State n
(doStuff) . (mkState) <===> (forall n. Num n => State n -> State n) . (Num n => n -> State n)
Hopefully the parentheses help make it clear here, the n from forall n. Num n ... for doStuff is a different type variable from the Num n => ... for mkState because the scope of the forall only extends to the end of the parentheses. So these functions can't actually compose because the compiler sees them as separate types! There are actually special rules for the $ operator specifically for using the ST monad precisely for this reason, just so you can do runST $ do ....
You may be able to accomplish what you want easier using GADTs, but I don't believe lens' TemplateHaskell will work with GADT types. However, you can write your own pretty easily in this case, so it isn't that big of a deal.
A further explanation:
doStuff . mkState $ 5.5
is very different than
doStuff $ mkState 5.5
In the first one, doStuff says that for all Num types n, its type is State n -> State n, whereas mkState says for some Num type m, its type is m -> State m. These two types are not the same because of the "for all" and "for some" quantifications (hence ExistentialQuantification), since composing them would mean that for some Num m you can produce all Num n.
In the doStuff $ mkState 5.5, you have the equivalent of
(forall n. Num n => State n -> State n) $ (Num m => State m)
Notice that the type after the $ is not a function because mkState 5.5 is fully applied. So this works because for all Num n you can do State n -> State n, and you're providing it some Num m => State m. This works intuitively. Again, the difference here is the composition versus application. You can't compose a function that works on some types with a function that works on all types, but you can pass a value to a function that works on all types ("all types" here meaning forall n. Num n => n).

When are type signatures necessary in Haskell?

Many introductory texts will tell you that in Haskell type signatures are "almost always" optional. Can anybody quantify the "almost" part?
As far as I can tell, the only time you need an explicit signature is to disambiguate type classes. (The canonical example being read . show.) Are there other cases I haven't thought of, or is this it?
(I'm aware that if you go beyond Haskell 2010 there are plenty for exceptions. For example, GHC will never infer rank-N types. But rank-N types are a language extension, not part of the official standard [yet].)
Polymorphic recursion needs type annotations, in general.
f :: (a -> a) -> (a -> b) -> Int -> a -> b
f f1 g n x =
if n == (0 :: Int)
then g x
else f f1 (\z h -> g (h z)) (n-1) x f1
(Credit: Patrick Cousot)
Note how the recursive call looks badly typed (!): it calls itself with five arguments, despite f having only four! Then remember that b can be instantiated with c -> d, which causes an extra argument to appear.
The above contrived example computes
f f1 g n x = g (f1 (f1 (f1 ... (f1 x))))
where f1 is applied n times. Of course, there is a much simpler way to write an equivalent program.
Monomorphism restriction
If you have MonomorphismRestriction enabled, then sometimes you will need to add a type signature to get the most general type:
{-# LANGUAGE MonomorphismRestriction #-}
-- myPrint :: Show a => a -> IO ()
myPrint = print
main = do
myPrint ()
myPrint "hello"
This will fail because myPrint is monomorphic. You would need to uncomment the type signature to make it work, or disable MonomorphismRestriction.
Phantom constraints
When you put a polymorphic value with a constraint into a tuple, the tuple itself becomes polymorphic and has the same constraint:
myValue :: Read a => a
myValue = read "0"
myTuple :: Read a => (a, String)
myTuple = (myValue, "hello")
We know that the constraint affects the first part of the tuple but does not affect the second part. The type system doesn't know that, unfortunately, and will complain if you try to do this:
myString = snd myTuple
Even though intuitively one would expect myString to be just a String, the type checker needs to specialize the type variable a and figure out whether the constraint is actually satisfied. In order to make this expression work, one would need to annotate the type of either snd or myTuple:
myString = snd (myTuple :: ((), String))
In Haskell, as I'm sure you know, types are inferred. In other words, the compiler works out what type you want.
However, in Haskell, there are also polymorphic typeclasses, with functions that act in different ways depending on the return type. Here's an example of the Monad class, though I haven't defined everything:
class Monad m where
return :: a -> m a
(>>=) :: m a -> (a -> m b) -> m b
fail :: String -> m a
We're given a lot of functions with just type signatures. Our job is to make instance declarations for different types that can be treated as Monads, like Maybe t or [t].
Have a look at this code - it won't work in the way we might expect:
return 7
That's a function from the Monad class, but because there's more than one Monad, we have to specify what return value/type we want, or it automatically becomes an IO Monad. So:
return 7 :: Maybe Int
-- Will return...
Just 7
return 6 :: [Int]
-- Will return...
[6]
This is because [t] and Maybe have both been defined in the Monad type class.
Here's another example, this time from the random typeclass. This code throws an error:
random (mkStdGen 100)
Because random returns something in the Random class, we'll have to define what type we want to return, with a StdGen object tupelo with whatever value we want:
random (mkStdGen 100) :: (Int, StdGen)
-- Returns...
(-3650871090684229393,693699796 2103410263)
random (mkStdGen 100) :: (Bool, StdGen)
-- Returns...
(True,4041414 40692)
This can all be found at learn you a Haskell online, though you'll have to do some long reading. This, I'm pretty much 100% certain, it the only time when types are necessary.

Haskell: list of elements with class restriction

here's my question:
this works perfectly:
type Asdf = [Integer]
type ListOfAsdf = [Asdf]
Now I want to do the same but with the Integral class restriction:
type Asdf2 a = (Integral a) => [a]
type ListOfAsdf2 = (Integral a) => [Asdf2 a]
I got this error:
Illegal polymorphic or qualified type: Asdf2 a
Perhaps you intended to use -XImpredicativeTypes
In the type synonym declaration for `ListOfAsdf2'
I have tried a lot of things but I am still not able to create a type with a class restriction as described above.
Thanks in advance!!! =)
Dak
Ranting Against the Anti-Existentionallists
I always dislike the anti-existential type talk in Haskell as I often find existentials useful. For example, in some quick check tests I have code similar to (ironically untested code follows):
data TestOp = forall a. Testable a => T String a
tests :: [TestOp]
tests = [T "propOne:" someProp1
,T "propTwo:" someProp2
]
runTests = mapM runTest tests
runTest (T s a) = putStr s >> quickCheck a
And even in a corner of some production code I found it handy to make a list of types I'd need random values of:
type R a = Gen -> (a,Gen)
data RGen = forall a. (Serialize a, Random a) => RGen (R a)
list = [(b1, str1, random :: RGen (random :: R Type1))
,(b2, str2, random :: RGen (random :: R Type2))
]
Answering Your Question
{-# LANGUAGE ExistentialQuantification #-}
data SomeWrapper = forall a. Integral a => SW a
If you need a context, the easiest way would be to use a data declaration:
data (Integral a) => IntegralData a = ID [a]
type ListOfIntegralData a = [IntegralData a]
*Main> :t [ ID [1234,1234]]
[ID [1234,1234]] :: Integral a => [IntegralData a]
This has the (sole) effect of making sure an Integral context is added to every function that uses the IntegralData data type.
sumID :: Integral a => IntegralData a -> a
sumID (ID xs) = sum xs
The main reason a type synonym isn't working for you is that type synonyms are designed as
just that - something that replaces a type, not a type signature.
But if you want to go existential the best way is with a GADT, because it handles all the quantification issues for you:
{-# LANGUAGE GADTs #-}
data IntegralGADT where
IG :: Integral a => [a] -> IntegralGADT
type ListOfIG = [ IntegralGADT ]
Because this is essentially an existential type, you can mix them up:
*Main> :t [IG [1,1,1::Int], IG [234,234::Integer]]
[IG [1,1,1::Int],IG [234,234::Integer]] :: [ IntegralGADT ]
Which you might find quite handy, depending on your application.
The main advantage of a GADT over a data declaration is that when you pattern match, you implicitly get the Integral context:
showPointZero :: IntegralGADT -> String
showPointZero (IG xs) = show $ (map fromIntegral xs :: [Double])
*Main> showPointZero (IG [1,2,3])
"[1.0,2.0,3.0]"
But existential quantification is sometimes used for the wrong reasons,
(eg wanting to mix all your data up in one list because that's what you're
used to from dynamically typed languages, and you haven't got used to
static typing and its advantages yet).
Here I think it's more trouble than it's worth, unless you need to mix different
Integral types together without converting them. I can't see a reason
why this would help, because you'll have to convert them when you use them.
For example, you can't define
unIG (IG xs) = xs
because it doesn't even type check. Rule of thumb: you can't do stuff that mentions the type a on the right hand side.
However, this is OK because we convert the type a:
unIG :: Num b => IntegralGADT -> [b]
unIG (IG xs) = map fromIntegral xs
Here existential quantification has forced you convert your data when I think your original plan was to not have to!
You may as well convert everything to Integer instead of this.
If you want things simple, keep them simple. The data declaration is the simplest way of ensuring you don't put data in your data type unless it's already a member of some type class.

Resources