Unable to figure out what the type of a function is - haskell

I have this function:
import Data.Aeson
import Network.HTTP.Conduit
getJSON url = eitherDecode <$> simpleHttp url
which is called as:
maybeJson <- getJSON "https://abc.com" :: IO (Either String Value)
However, I can't figure out what the type of getJSON is. I've been trying these:
getJSON :: FromJSON a => String -> Either String a --1
getJSON :: String -> Either String Value --2
plus some other ones but failed. What is it?

The main thing you're missing in your attempts so far is the IO type. One correct type given your current usage is
getJSON :: String -> IO (Either String Value)
You can see that the IO type must be needed given your maybeJSON line - that makes it clear that getJSON <something> returns IO (Either String Value).
In fact the exact type is more general:
getJSON :: (FromJSON a, MonadIO m, Functor m) => String -> m (Either String a)
To go into more detail on how to derive the correct type, we need to look carefully at the types of simpleHttp and eitherDecode:
eitherDecode :: FromJSON a => ByteString -> Either String a
simpleHttp :: MonadIO m => String -> m ByteString
They're also being combined with (<$>) from Control.Applicative:
(<$>) :: Functor f => (a -> b) -> f a -> f b
Putting it all together gives the type above - the f for (<$>) and the m for simpleHttp must be the same, and the input type is the String being fed into simpleHttp, and the result type is the result type of eitherDecode, lifted into m by the (<$>) operation.
You can also just ask GHC to tell you the answer. Either load your module up in ghci and use :t getJSON, or leave out the type signature, compile with -Wall and look at the warning about the missing type signature for getJSON.

Note that you don't have to explicitly declare a type for your functions in Haskell. The compiler will deduce them for you. In fact, you can use the :type command (or just :t for short) in ghci to let the compiler tell you the type of a function after you load the source file.

Related

Why the newtype syntax creates a function

I look at this declaration:
newtype Parser a = Parser { parse :: String -> Maybe (a,String) }
Here is what I understand:
1) Parser is declared as a type with a type parameter a
2) You can instantiate Parser by providing a parser function for example p = Parser (\s -> Nothing)
What I observed is that suddenly I have a function name parse defined and it is capable of running Parsers.
For example, I can run:
parse (Parser (\s -> Nothing)) "my input"
and get Nothing as output.
How was this parse function got defined with this specific signature? How does this function "know" to execute the Parser given to it? Hope that someone can clear my confusion.
Thanks!
When you write newtype Parser a = Parser { parse :: String -> Maybe (a,String) } you introduce three things:
A type named Parser.
A term level constructor of Parsers named Parser. The type of this function is
Parser :: (String -> Maybe (a, String)) -> Parser a
You give it a function and it wraps it inside a Parser
A function named parse to remove the Parser wrapper and get your function back. The type of this function is:
parse :: Parser a -> String -> Maybe (a, String)
Check yourself in ghci:
Prelude> newtype Parser a = Parser { parse :: String -> Maybe (a,String) }
Prelude> :t Parser
Parser :: (String -> Maybe (a, String)) -> Parser a
Prelude> :t parse
parse :: Parser a -> String -> Maybe (a, String)
Prelude>
It's worth nothing that the term level constructor (Parser) and the function to remove the wrapper (parse) are both arbitrary names and don't need to match the type name. It's common for instance to write:
newtype Parser a = Parser { unParser :: String -> Maybe (a,String) }
this makes it clear unParse removes the wrapper around the parsing function. However, I recommend your type and constructor have the same name when using newtypes.
How does this function "know" to execute the Parser given to it
You are unwrapping the function using parse and then calling the unwrapped function with "myInput".
First, let’s have a look at a parser newtype without record syntax:
newtype Parser' a = Parser' (String -> Maybe (a,String))
It should be obvious what this type does: it stores a function String -> Maybe (a,String). To run this parser, we will need to make a new function:
runParser' :: Parser' a -> String -> Maybe (a,String)
runParser' (Parser' p) i = p i
And now we can run parsers like runParser' (Parser' $ \s -> Nothing) "my input".
But now note that, since Haskell functions are curried, we can simply remove the reference to the input i to get:
runParser'' :: Parser' a -> (String -> Maybe (a,String))
runParser'' (Parser' p) = p
This function is exactly equivalent to runParser', but you could think about it differently: instead of applying the parser function to the value explicitly, it simply takes a parser and fetches the parser function from it; however, thanks to currying, runParser'' can still be used with two arguments.
Now, let’s go back to back to your original type:
newtype Parser a = Parser { parse :: String -> Maybe (a,String) }
The only difference between your type and mine is that your type uses record syntax, although it may be a bit hard to recognise since a newtype can only have one field; this record syntax automatically defines a function parse :: Parser a -> (String -> Maybe (a,String)), which extracts the String -> Maybe (a,String) function from the Parser a. Hopefully the rest should be obvious: thanks to currying, parse can be used with two arguments rather than one, and this simply has the effect of running the function stored within the Parser a. In other words, your definition is exactly equivalent to the following code:
newtype Parser a = Parser (String -> Maybe (a,String))
parse :: Parser a -> (String -> Maybe (a,String))
parse (Parser p) = p

RPC (Or: How do I disambiguate function application based on TypeRep values?)

I'm building some infrastructure for doing remote procedure calls in Haskell, and for reasons that are too long to explain here, I cannot reuse existing libraries.
So here's the setup: I have a type class for serializing and deserializing data:
class Serializable a where
encode :: a -> B.ByteString
decode :: B.ByteString -> Maybe a
maxSize :: a -> Int
where B is Data.ByteString.
I can use this to implement serialization of integers, booleans, lists of serializables, tuples of serializables ect.
Now I want to send some arguments across a network to a server, which then performs a computation based on these arguments, and sends back a result. So I create an existential type representing things that can be serialized:
data SerializableExt = forall t . Serializable t => SerializableExt t
because I want to send something of type [SerializableExt].
So, of course, I need to create an instance Serializable SerializableExt. This is where the problem starts:
In order to implement decode :: B.ByteString -> Maybe SerializableExt I need to know the concrete type that the existential type SerializableExt wraps.
So I implement encode :: SerializableExt -> B.ByteString as serializing the concrete type along with the value:
encode (SerializableExt x) = encode (typeOf x, x)
using typeOf from Data-Typeable. The problem is now the implementation of decode :: B.ByteString -> Maybe SerializableExt:
decode bs =
let (tyenc, xenc) = splitPair bs -- Not really important. It just splits bs into the two components
in case (decode tyenc :: Maybe TypeRep) of
Just ty -> SerializableExt <$> _ -- Somehow invoke decode xenc, where the choice of which decode to execute depends on the value of ty.
_ -> Nothing
But I can't see how to fill in the hole here. Because of Haskell's separation of the value level and the type level I can't use the value of ty to disambiguate the invocation of decode xenc, right?
Is there a way to solve this issue, and actually put something in the hole which will do what I want? Or can you come up with another design?
EDIT: One way of doing it would be the following:
decode bs =
let (tyenc, xenc) = splitPair bs
in SerializableExt <$>
case (decode tyenc :: Maybe TypeRep) of
Just ty
| ty == typeRep (Proxy :: Proxy Int) -> decode xenc :: Maybe Int
| ty = typeRep (Proxy :: Proxy ()) -> decode xenc :: Maybe ()
| ...
_ -> Nothing
but this is bad for several reasons:
It's tedious to extend.
It cannot handle pairs (or generally: tuples) generically; every
combination of types needs to be handled.
It's not very Haskelly
Data.Dynamic lets us put arbitrary Haskell values into a single container, and get them out again in a type-safe way. That's a good start towards inter-process communication; I'll come back to serialization below.
We can write a program that takes a list of Dynamic values, checks for the number & types it needs, and returns a result in the same way.
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-}
-- | Experiments with type-safe serialization.
module Main where
import Data.Proxy
import Data.Dynamic
import Data.Foldable
import Data.Type.Equality
import Type.Reflection
foo :: Int -> String -> String
foo i s = concat (replicate i s)
actor :: [Dynamic] -> Either String [Dynamic]
actor (di : ds : _) = case (fromDynamic di, fromDynamic ds) of
(Just i, Just s) -> Right [toDyn (foo i s)]
_ -> Left "Wrong types of arguments"
actor _ = Left "Not enough arguments"
caller :: Either String [Dynamic]
caller = actor [ toDyn (3::Int), toDyn "bar" ]
main :: IO ()
main = case caller of
Left err -> putStrLn err
Right dyns -> for_ dyns (\d -> case fromDynamic d of
Just s -> putStrLn s
Nothing -> print d)
We can use a TypeRep to guide selection of a class instance. (For ease of testing my code, I used String.)
class Serial a where
encode :: a -> String
decode :: String -> Maybe a
decodeAs :: Serial a => TypeRep a -> String -> Maybe a
decodeAs _ s = decode s
Finally, we'd like to serialize the TypeRep, and when decoding, check that the encoded type matches the type that we're decoding at.
instance Serial SomeTypeRep
encodeDyn :: (Typeable a, Serial a) => a -> (String, String)
encodeDyn a = (encode (SomeTypeRep (typeOf a)), encode a)
decodeDynamic :: forall a. (Typeable a, Serial a) => String -> String -> Maybe a
decodeDynamic tyStr aStr = case decode tyStr of
Nothing -> Nothing
Just (SomeTypeRep ty) ->
case eqTypeRep ty (typeRep :: TypeRep a) of
Nothing -> Nothing
Just HRefl -> decodeAs ty aStr

Understanding types in the streaming libarary

In regards to the streaming libarary What is m in Stream (Of a) m r? How could I figure this out from the documentation (sorry, a noob here)?
I'd like to understand what the type means so that I can work out my specific problem where I'm creating a stream of requests using servant, and while trying to consume it like this:
post :: Maybe Int -> ClientM [BlogPost]
post = ...
stream :: Stream (Of (ClientM [BlogPost])) ClientM ()
stream = S.map posts $ S.each $ [Just p | p <- [1..5]]
main = do
let url = ...
S.print $ S.map (\x -> runClientM x url) stream
But I'm getting the following error:
• Couldn't match type ‘ClientM’ with ‘IO’
Expected type: S.Stream (S.Of (ClientM [BlogPost])) IO ()
Actual type: S.Stream (S.Of (ClientM [BlogPost])) ClientM ()
If given in isolation, the m in Stream (Of a) m r could be any type.
When considering specific functions in the module, be aware of the type constraint. For example, the yield function has this type:
yield :: Monad m => a -> Stream (Of a) m ()
Here, m is constrained to be any type that's a Monad instance. This could be IO, [] (list), Maybe, State, Reader, etc.
Another function has this type:
stdinLn :: MonadIO m => Stream (Of String) m ()
Here, m is constrained to be any type that's a MonadIO instance. The MonadIO type class is a subclass of Monad, in the sense that for a type to be a MonadIO, it must already be a Monad.
AFAICT, IO is also a MonadIO, but e.g. Maybe isn't.
Thus, some of the functions in the module are more constrained than others. The yield function is less constrained than the stdinLn function. You can use Maybe as m with yield, but not with stdinLn.
Regarding your specific problem, there's not enough information in the OP for a repro, but it looks like main uses the map function from Streaming.Prelude:
map :: Monad m => (a -> b) -> Stream (Of a) m r -> Stream (Of b) m r
Here, m must be a Monad instance. In Haskell, the main function must have the type IO (), so when using do notation, the Monad instance is inferred to be IO. The error message states that the compiler expects m to be IO.

Haskell: function signature

This program compiles without problems:
bar :: MonadIO m
=> m String
bar = undefined
run2IO :: MonadIO m
=> m String
-> m String
run2IO foo = liftIO bar
When I change bar to foo (argument name),
run2IO :: MonadIO m
=> m String
-> m String
run2IO foo = liftIO foo
I get:
Couldn't match type ‘m’ with ‘IO’
‘m’ is a rigid type variable bound by
the type signature for run2IO :: MonadIO m => m String -> m String
...
Expected type: IO String
Actual type: m String ...
Why are the 2 cases are not equivalent?
Remember the type of liftIO:
liftIO :: MonadIO m => IO a -> m a
Importantly, the first argument must be a concrete IO value. That means when you have an expression liftIO x, then x must be of type IO a.
When a Haskell function is universally quantified (using an implicit or explicit forall), then that means the function caller chooses what the type variable is replaced by. As an example, consider the id function: it has type a -> a, but when you evaluate the expression id True, then id takes the type Bool -> Bool because a is instantiated as the Bool type.
Now, consider your first example again:
run2IO :: MonadIO m => m Integer -> m Integer
run2IO foo = liftIO bar
The foo argument is completely irrelevant here, so all that actually matters is the liftIO bar expression. Since liftIO requires its first argument to be of type IO a, then bar must be of type IO a. However, bar is polymorphic: it actually has type MonadIO m => m Integer.
Fortunately, IO has a MonadIO instance, so the bar value is instantiated using IO to become IO Integer, which is okay, because bar is universally quantified, so its instantiation is chosen by its use.
Now, consider the other situation, in which liftIO foo is used, instead. This seems like it’s the same, but it actually isn’t at all: this time, the MonadIO m => m Integer value is an argument to the function, not a separate value. The quantification is over the entire function, not the individual value. To understand this more intuitively, it might be helpful to consider id again, but this time, consider its definition:
id :: a -> a
id x = x
In this case, x cannot be instantiated to be Bool within its definition, since that would mean id could only work on Bool values, which is obviously wrong. Effectively, within the implementation of id, x must be used completely generically—it cannot be instantiated to a specific type because that would violate the parametricity guarantees.
Therefore, in your run2IO function, foo must be used completely generically as an arbitrary MonadIO value, not a specific MonadIO instance. The liftIO call attempts to use the specific IO instance, which is disallowed, since the caller might not provide an IO value.
It is possible, of course, that you might want the argument to the function to be quantified in the same way as bar is; that is, you might want its instantiation to be chosen by the implementation, not the caller. In that case, you can use the RankNTypes language extension to specify a different type using an explicit forall:
{-# LANGUAGE RankNTypes #-}
run3IO :: MonadIO m => (forall m1. MonadIO m1 => m1 Integer) -> m Integer
run3IO foo = liftIO foo
This will typecheck, but it’s not a very useful function.
In the first, you're using liftIO on bar. That actually requires bar :: IO String. Now, IO happens to be (trivially) an instance on MonadIO, so this works – the compiler simply throws away the polymorphism of bar.
In the second case, the compiler doesn't get to decide what particular monad to use as the type of foo: it's fixed by the environment, i.e. the caller can decide what MonadIO instance it should be. To again get the freedom to choose IO as the monad, you'd need the following signature:
{-# LANGUAGE Rank2Types, UnicodeSyntax #-}
run2IO' :: MonadIO m
=> (∀ m' . MonadIO m' => m' String)
-> m String
run2IO' foo = liftIO foo
... however I don't think you really want that: you might then as well write
run2IO' :: MonadIO m => IO String -> m String
run2IO' foo = liftIO foo
or simply run2IO = liftIO.

Type signature "Maybe a" doesn't like "Just [Event]"

I'm still learning Haskell and need help with the type inference please!
Using packages SDL and Yampa
I get the following type signature from FRP.Yampa.reactimate:
(Bool -> IO (DTime, Maybe a))
and I want to use it for:
myInput :: Bool -> IO (DTime, Maybe [SDL.Event])
myInput isBlocking = do
event <- SDL.pollEvent
return (1, Just [event])
...
reactimate myInit myInput myOutput mySF
but it says
Couldn't match expected type `()'
against inferred type `[SDL.Event]'
Expected type: IO (DTime, Maybe ())
Inferred type: IO (DTime, Maybe [SDL.Event])
In the second argument of `reactimate', namely `input'
In the expression: reactimate initialize input output process
I thought Maybe a allows me to use anything, even a SDL.Event list?
Why is it expecting Maybe () when the type signature is actually Maybe a?
Why does it want an empty tuple, or a function taking no arguments, or what is () supposed to be?
The full type signature of reactimate is
IO a -- # myInit
-> (Bool -> IO (DTime, Maybe a)) -- # myInput
-> (Bool -> b -> IO Bool) -- # myOutput
-> SF a b -- # mySF
-> IO ()
The same a and b must match, that means if your myInput has type Bool -> IO (DTime, Maybe [SDL.Event]), then all other a must also be [SDL.Event]. Hence, to match the types, you need to ensure
myInit :: IO [SDL.Event] -- # **not** IO ().
mySF :: SF [SDL.Event] b
BTW, () is the unit type.

Resources