`No instance for System.Random.Random` on a custom typeclass when using `choose` - haskell

I am doing an exercise in Haskell Programming from First Principles. It asks me to generate equal probabilities, and 1/3, 2/3 probabilities from each of:
data Fool =
Fulse
| Frue
deriving (Eq, Show)
And my answer is
module Random where
-- import Test.Hspec
import Test.QuickCheck
data Fool =
Fulse
| Frue
deriving (Eq, Show)
genFool :: Gen Fool
genFool = choose (Fulse, Frue)
genFool' :: Gen Fool
genFool' = do
frequency [(2, return Fulse)
,(1, return Frue)]
but genFool is wrong. The error message is :
../chap14/random.hs:13:11: error:
• No instance for (System.Random.Random Fool)
arising from a use of ‘choose’
• In the expression: choose (Fulse, Frue)
In an equation for ‘genFool’: genFool = choose (Fulse, Frue)
|
13 | genFool = choose (Fulse, Frue)
| ^^^^^^^^^^^^^^^^^^^^
Previously I have some code like this:
genBool :: Gen Bool
genBool = choose (False, True)
which works properly. I think there may be some predefined instance of System.Random.Random Fool to make the choose work.
What should I do to make the my version of genFool compile?
And btw, why is the return Fulse in the second genFool' of type Gen Fool?

The Test.Quickcheck module's choose function has the following type signature:
choose :: Random a => (a, a) -> Gen a
So, if you are planning to use choose function on your Fool type, it has to be made instance of Random typeclass as seen in the above type signature.
This is where Random typeclass is defined. It needs either a minimal implementation of either randomR and random.
Since your type Fool has only two values, it's isomorphic to Bool type. So, you can define a function mapping the values appropriately:
mapBool :: Bool -> Fool
mapBool False = Fulse
mapBool True = Frue
And then you can define a typeclass instance for your type:
instance Random Fool where
random g = let (b :: Bool, g') = random g
in (mapBool b, g')
randomR _ g = (random g) -- Note that this doesn't work correctly. You need to pattern match and fix this.
The above code should make your module compile fine.

Related

Deriving Eq and Show for an ADT that contains fields that can't have Eq or Show

I'd like to be able to derive Eq and Show for an ADT that contains multiple fields. One of them is a function field. When doing Show, I'd like it to display something bogus, like e.g. "<function>"; when doing Eq, I'd like it to ignore that field. How can I best do this without hand-writing a full instance for Show and Eq?
I don't want to wrap the function field inside a newtype and write my own Eq and Show for that - it would be too bothersome to use like that.
One way you can get proper Eq and Show instances is to, instead of hard-coding that function field, make it a type parameter and provide a function that just “erases” that field. I.e., if you have
data Foo = Foo
{ fooI :: Int
, fooF :: Int -> Int }
you change it to
data Foo' f = Foo
{ _fooI :: Int
, _fooF :: f }
deriving (Eq, Show)
type Foo = Foo' (Int -> Int)
eraseFn :: Foo -> Foo' ()
eraseFn foo = foo{ fooF = () }
Then, Foo will still not be Eq- or Showable (which after all it shouldn't be), but to make a Foo value showable you can just wrap it in eraseFn.
Typically what I do in this circumstance is exactly what you say you don’t want to do, namely, wrap the function in a newtype and provide a Show for that:
data T1
{ f :: X -> Y
, xs :: [String]
, ys :: [Bool]
}
data T2
{ f :: OpaqueFunction X Y
, xs :: [String]
, ys :: [Bool]
}
deriving (Show)
newtype OpaqueFunction a b = OpaqueFunction (a -> b)
instance Show (OpaqueFunction a b) where
show = const "<function>"
If you don’t want to do that, you can instead make the function a type parameter, and substitute it out when Showing the type:
data T3' a
{ f :: a
, xs :: [String]
, ys :: [Bool]
}
deriving (Functor, Show)
newtype T3 = T3 (T3' (X -> Y))
data Opaque = Opaque
instance Show Opaque where
show = const "..."
instance Show T3 where
show (T3 t) = show (Opaque <$ t)
Or I’ll refactor my data type to derive Show only for the parts I want to be Showable by default, and override the other parts:
data T4 = T4
{ f :: X -> Y
, xys :: T4' -- Move the other fields into another type.
}
instance Show T4 where
show (T4 f xys) = "T4 <function> " <> show xys
data T4' = T4'
{ xs :: [String]
, ys :: [Bool]
}
deriving (Show) -- Derive ‘Show’ for the showable fields.
Or if my type is small, I’ll use a newtype instead of data, and derive Show via something like OpaqueFunction:
{-# LANGUAGE DerivingVia #-}
newtype T5 = T5 (X -> Y, [String], [Bool])
deriving (Show) via (OpaqueFunction X Y, [String], [Bool])
You can use the iso-deriving package to do this for data types using lenses if you care about keeping the field names / record accessors.
As for Eq (or Ord), it’s not a good idea to have an instance that equates values that can be observably distinguished in some way, since some code will treat them as identical and other code will not, and now you’re forced to care about stability: in some circumstance where I have a == b, should I pick a or b? This is why substitutability is a law for Eq: forall x y f. (x == y) ==> (f x == f y) if f is a “public” function that upholds the invariants of the type of x and y (although floating-point also violates this). A better choice is something like T4 above, having equality only for the parts of a type that can satisfy the laws, or explicitly using comparison modulo some function at use sites, e.g., comparing someField.
The module Text.Show.Functions in base provides a show instance for functions that displays <function>. To use it, just:
import Text.Show.Functions
It just defines an instance something like:
instance Show (a -> b) where
show _ = "<function>"
Similarly, you can define your own Eq instance:
import Text.Show.Functions
instance Eq (a -> b) where
-- all functions are equal...
-- ...though some are more equal than others
_ == _ = True
data Foo = Foo Int Double (Int -> Int) deriving (Show, Eq)
main = do
print $ Foo 1 2.0 (+1)
print $ Foo 1 2.0 (+1) == Foo 1 2.0 (+2) -- is True
This will be an orphan instance, so you'll get a warning with -Wall.
Obviously, these instances will apply to all functions. You can write instances for a more specialized function type (e.g., only for Int -> String, if that's the type of the function field in your data type), but there is no way to simultaneously (1) use the built-in Eq and Show deriving mechanisms to derive instances for your datatype, (2) not introduce a newtype wrapper for the function field (or some other type polymorphism as mentioned in the other answers), and (3) only have the function instances apply to the function field of your data type and not other function values of the same type.
If you really want to limit applicability of the custom function instances without a newtype wrapper, you'd probably need to build your own generics-based solution, which wouldn't make much sense unless you wanted to do this for a lot of data types. If you go this route, then the Generics.Deriving.Show and Generics.Deriving.Eq modules in generic-deriving provide templates for these instances which could be modified to treat functions specially, allowing you to derive per-datatype instances using some stub instances something like:
instance Show Foo where showsPrec = myGenericShowsPrec
instance Eq Foo where (==) = myGenericEquality
I proposed an idea for adding annotations to fields via fields, that allows operating on behaviour of individual fields.
data A = A
{ a :: Int
, b :: Int
, c :: Int -> Int via Ignore (Int->Int)
}
deriving
stock GHC.Generic
deriving (Eq, Show)
via Generically A -- assuming Eq (Generically A)
-- Show (Generically A)
But this is already possible with the "microsurgery" library, but you might have to write some boilerplate to get it going. Another solution is to write separate behaviour in "sums-of-products style"
data A = A Int Int (Int->Int)
deriving
stock GHC.Generic
deriving
anyclass SOP.Generic
deriving (Eq, Show)
via A <-𝈖-> '[ '[ Int, Int, Ignore (Int->Int) ] ]

Set specific properties for data in Haskell

Let us say I want to make a ADT as follows in Haskell:
data Properties = Property String [String]
deriving (Show,Eq)
I want to know if it is possible to give the second list a bounded and enumerated property? Basically the first element of the list will be the minBound and the last element will be the maxBound. I am trying,
data Properties a = Property String [a]
deriving (Show, Eq)
instance Bounded (Properties a) where
minBound a = head a
maxBound a = (head . reverse) a
But not having much luck.
Well no, you can't do quite what you're asking, but maybe you'll find inspiration in this other neat trick.
{-# language ScopedTypeVariables, FlexibleContexts, UndecidableInstances #-}
import Data.Reflection -- from the reflection package
import qualified Data.List.NonEmpty as NE
import Data.List.NonEmpty (NonEmpty (..))
import Data.Proxy
-- Just the plain string part
newtype Pstring p = P String deriving Eq
-- Those properties you're interested in. It will
-- only be possible to produce bounds if there's at
-- least one property, so NonEmpty makes more sense
-- than [].
type Props = NonEmpty String
-- This is just to make a Show instance that does
-- what you seem to want easier to write. It's not really
-- necessary.
data Properties = Property String [String] deriving Show
Now we get to the key part, where we use reflection to produce class instances that can depend on run-time values. Roughly speaking, you can think of
Reifies x t => ...
as being a class-level version of
\(x :: t) -> ...
Because it operates at the class level, you can use it to parametrize instances. Since Reifies x t binds a type variable x, rather than a term variable, you need to use reflect to actually get the value back. If you happen to have a value on hand whose type ends in p, then you can just apply reflect to that value. Otherwise, you can always magic up a Proxy :: Proxy p to do the job.
-- If some Props are "in the air" tied to the type p,
-- then we can show them along with the string.
instance Reifies p Props => Show (Pstring p) where
showsPrec k p#(P str) =
showsPrec k $ Property str (NE.toList $ reflect p)
-- If some Props are "in the air" tied to the type p,
-- then we can give Pstring p a Bounded instance.
instance Reifies p Props => Bounded (Pstring p) where
minBound = P $ NE.head (reflect (Proxy :: Proxy p))
maxBound = P $ NE.last (reflect (Proxy :: Proxy p))
Now we need to have a way to actually bind types that can be passed to the type-level lambdas. This is done using the reify function. So let's throw some Props into the air and then let the butterfly nets get them back.
main :: IO ()
main = reify ("Hi" :| ["how", "are", "you"]) $
\(_ :: Proxy p) -> do
print (minBound :: Pstring p)
print (maxBound :: Pstring p)
./dfeuer#squirrel:~/src> ./WeirdBounded
Property "Hi" ["Hi","how","are","you"]
Property "you" ["Hi","how","are","you"]
You can think of reify x $ \(p :: Proxy p) -> ... as binding a type p to the value x; you can then pass the type p where you like by constraining things to have types involving p.
If you're just doing a couple of things, all this machinery is way more than necessary. Where it gets nice is when you're performing lots of operations with values that have phantom types carrying extra information. In many cases, you can avoid most of the explicit applications of reflect and the explicit proxy handling, because type inference just takes care of it all for you. For a good example of this technique in action, see the hyperloglog package. Configuration information for the HyperLogLog data structure is carried in a type parameter; this guarantees, at compile time, that only similarly configured structures are merged with each other.

Haskell type checking in code

Could you please show me how can I check if type of func is Tree or not, in code not in command page?
data Tree = Leaf Float | Gate [Char] Tree Tree deriving (Show, Eq, Ord)
func a = Leaf a
Well, there are a few answers, which zigzag in their answers to "is this possible".
You could ask ghci
ghci> :t func
func :: Float -> Tree
which tells you the type.
But you said in your comment that you are wanting to write
if func == Tree then 0 else 1
which is not possible. In particular, you can't write any function like
isTree :: a -> Bool
isTree x = if x :: Tree then True else False
because it would violate parametericity, which is a neat property that all polymorphic functions in Haskell have, which is explored in the paper Theorems for Free.
But you can write such a function with some simple generic mechanisms that have popped up; essentially, if you want to know the type of something at runtime, it needs to have a Typeable constraint (from the module Data.Typeable). Almost every type is Typeable -- we just use the constraint to indicate the violation of parametericity and to indicate to the compiler that it needs to pass runtime type information.
import Data.Typeable
import Data.Maybe (isJust)
data Tree = Leaf Float | ...
deriving (Typeable) -- we need Trees to be typeable for this to work
isTree :: (Typeable a) => a -> Bool
isTree x = isJust (cast x :: Maybe Tree)
But from my experience, you probably don't actually need to ask this question. In Haskell this question is a lot less necessary than in other languages. But I can't be sure unless I know what you are trying to accomplish by asking.
Here's how to determine what the type of a binding is in Haskell: take something like f a1 a2 a3 ... an = someExpression and turn it into f = \a1 -> \a2 -> \a3 -> ... \an -> someExpression. Then find the type of the expression on the right hand side.
To find the type of an expression, simply add a SomeType -> for each lambda, where SomeType is whatever the appropriate type of the bound variable is. Then use the known types in the remaining (lambda-less) expression to find its actual type.
For your example: func a = Leaf a turns into func = \a -> Leaf a. Now to find the type of \a -> Leaf a, we add a SomeType -> for the lambda, where SomeType is Float in this case. (because Leaf :: Float -> Tree, so if Leaf is applied to a, then a :: Float) This gives us Float -> ???
Now we find the type of the lambda-less expression Leaf (a :: Float), which is Tree because Leaf :: Float -> Tree. Now we can add substitute Tree for ??? to get Float -> Tree, the actual type of func.
As you can see, we did that all by just looking at the source code. This means that no matter what, func will always have that type, so there is no need to check whether or not it does. In fact, the compiler will throw out all information about the type of func when it compiles your code, and your code will still work properly because of type-checking. (The caveat to this (Typeable) is pointed out in the other answer)
TL;DR: Haskell is statically typed, so func always has the type Float -> Tree, so asking how to check whether that is true doesn't make sense.

Does exporting type constructors make a difference?

Let's say I have an internal data type, T a, that is used in the signature of exported functions:
module A (f, g) where
newtype T a = MkT { unT :: (Int, a) }
deriving (Functor, Show, Read) -- for internal use
f :: a -> IO (T a)
f a = fmap (\i -> T (i, a)) randomIO
g :: T a -> a
g = snd . unT
What is the effect of not exporting the type constructor T? Does it prevent consumers from meddling with values of type T a? In other words, is there a difference between the export list (f, g) and (f, g, T()) here?
Prevented
The first thing a consumer will see is that the type doesn't appear in Haddock documentation. In the documentation for f and g, the type Twill not be hyperlinked like an exported type. This may prevent a casual reader from discovering T's class instances.
More importantly, a consumer cannot doing anything with T at the type level. Anything that requires writing a type will be impossible. For instance, a consumer cannot write new class instances involving T, or include T in a type family. (I don't think there's a way around this...)
At the value level, however, the main limitation is that a consumer cannot write a type annotation including T:
> :t (f . read) :: Read b => String -> IO (A.T b)
<interactive>:1:39: Not in scope: type constructor or class `A.T'
Not prevented
The restriction on type signatures is not as significant a limitation as it appears. The compiler can still infer such a type:
> :t f . read
f . read :: Read b => String -> IO (A.T b)
Any value expression within the inferrable subset of Haskell may therefore be expressed regardless of the availability of the type constructor T. If, like me, you're addicted to ScopedTypeVariables and extensive annotations, you may be a little surprised by the definition of unT' below.
Furthermore, because typeclass instances have global scope, a consumer can use any available class functions without additional limitation. Depending on the classes involved, this may allow significant manipulation of values of the unexposed type. With classes like Functor, a consumer can also freely manipulate type parameters, because there's an available function of type T a -> T b.
In the example of T, deriving Show of course exposes the "internal" Int, and gives a consumer enough information to hackishly implement unT:
-- :: (Show a, Read a) => T a -> (Int, a)
unT' = (read . strip . show') `asTypeOf` (mkPair . g)
where
strip = reverse . drop 1 . reverse . drop 9
-- :: T a -> String
show' = show `asTypeOf` (mkString . g)
mkPair :: t -> (Int, t)
mkPair = undefined
mkString :: t -> String
mkString = undefined
> :t unT'
unT' :: (Show b, Read b) => A.T b -> (Int, b)
> x <- f "x"
> unT' x
(-29353, "x")
Implementing mkT' with the Read instance is left as an exercise.
Deriving something like Generic will completely explode any idea of containment, but you'd probably expect that.
Prevented?
In the corners of Haskell where type signatures are necessary or where asTypeOf-style tricks don't work, I guess not exporting the type constructor could actually prevent a consumer from doing something they could with the export list (f, g, T()).
Recommendation
Export all type constructors that are used in the type of any value you export. Here, go ahead and include T() in your export list. Leaving it out doesn't accomplish anything other than muddying the documentation. If you want to expose an purely abstract immutable type, use a newtype with a hidden constructor and no class instances.

Haskell: Type safety with logically different Boolean values

Lets say I've got the following code
type IsTall = Bool
type IsAlive = Bool
is_short_alive_person is_tall is_alive = (not is_tall) && is_alive
Say, later on, I've got the following
a :: IsAlive
a = False
b :: IsTall
b = True
And call the following, getting the two arguments around the wrong way:
is_short_alive_person a b
This successfully compiles unfortunately, and at runtime tall dead people are instead found instead of short alive people.
I would like the above example not to compile.
My first attempt was:
newtype IsAlive = IsAlive Bool
newtype IsTall = IsTall Bool
But then I can't do something like.
switch_height :: IsTall -> IsTall
switch_height h = not h
As not is not defined on IsTalls, only Bools.
I could explicitly extract the Bools all the time, but that largely defeats the purpose.
Basically, I want IsTalls to interact with other IsTalls, just like they're Bools, except they won't interact with Bools and IsAlives without an explicit cast.
What's the best way to achieve this.
p.s. I think I've achieved this with numbers by doing in GHC:
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
newtype UserID = UserID Int deriving (Eq, Ord, Num)
newtype GroupID = GroupID Int deriving (Eq, Ord, Num)
(i.e. UserID's and GroupID's shouldn't interact)
but I can't seem to do this with Bools (deriving Bool doesn't work). I'm not even sure the above is the best approach anyway.
If you change your data type slightly you can make it an instance of Functor and you can then use fmap to do operations on the Boolean
import Control.Applicative
newtype IsAliveBase a = IsAlive a
newtype IsTallBase a = IsTall a
type IsAlive = IsAliveBase Bool
type IsTall = IsTallBase Bool
instance Functor IsAliveBase where
fmap f (IsAlive b) = IsAlive (f b)
instance Functor IsTallBase where
fmap f (IsTall b) = IsTall (f b)
switch_height :: IsTall -> IsTall
switch_height h = not <$> h -- or fmap not h
-- EDIT
for operations like && you can make it an instance of Applicative
instance Applicative IsAliveBase where
pure = IsAlive
(IsAlive f) <*> (IsAlive x) = IsAlive (f x)
and then you can do (&&) using liftA2
example:
*Main> let h = IsAlive True
*Main> liftA2 (&&) h h
IsAlive True
you can read more about this at http://en.wikibooks.org/wiki/Haskell/Applicative_Functors
Your options are either to define algebraic data types like
data Height = Tall | Short
data Wiggliness = Alive | Dead
or to define new operators, e.g., &&&, |||, complement and to overload them on the type of your choice. But even with overloading you won't be able to use them with if.
I'm not sure that Boolean operations on height make sense anyway. How do you justify a conclusion that "tall and short equals short" but "tall or short equals tall"?
I suggest you look for different names for your connectives, which you can then overload.
P.S. Haskell is always getting new features, so the best I can say is that if you can overload if I'm not aware of it. To say about Haskell that "such-and-such can't be done" is always dangerous...
You can get some way towards this, using newtypes and a class if you import the Prelude hiding the boolean functions you want to use with your IsTall and IsAlive values. You redefine the boolean functions as methods in the class, for which you then make instances for all 3 of the Bool, IsTall, and IsAlive types. If you use GeneralizedNewtypeDeriving you can even get the IsTall and IsAlive instances without having to write the wrapping/unwrapping boilerplate by hand.
Here's an example script I actually tried out in ghci:
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
import Prelude hiding ((&&), (||), not)
import qualified Prelude
class Boolish a where
(&&) :: a -> a -> a
(||) :: a -> a -> a
not :: a -> a
instance Boolish Bool where
(&&) = (Prelude.&&)
(||) = (Prelude.||)
not = Prelude.not
newtype IsTall = IsTall Bool
deriving (Eq, Ord, Show, Boolish)
newtype IsAlive = IsAlive Bool
deriving (Eq, Ord, Show, Boolish)
You can now &&, ||, and not values of any of the three types, but not together. And they're separate types, so your function signatures can now restrict which of the 3 they want to accept.
Higher order functions defined in other modules will work fine with this, as in:
*Main> map not [IsTall True, IsTall False]
[IsTall False,IsTall True]
But you won't be able to pass an IsTall to any other function defined elsewhere that expects a Bool, because the other module will still be using the Prelude version of the boolean functions. Language constructs like if ... then ... else ... will still be a problem too (although a comment by hammar on Norman Ramsey's answer says you can fix this with another GHC extension). I'd probably add a toBool method to that class to help uniformly convert back to regular Bools to help mitigate such problems.

Resources