Function with type synonym - haskell

Sorry for asking as potentially silly question, but returning to Haskell to do some conversion from one database package to a different one, I find myself a bit puzzled about how to do this properly.
In the Database.SQLite3 module, there is an execWithCallback with type
execWithCallback :: Database -> Text -> ExecCallback -> IO ()
Now, the callback is defined as
type ExecCallback = ColumnCount -> [Text]-> [Maybe Text] -> IO ()
that is, a function with type ExecCallback
My silly test code compiles and runs correctly:
{-# LANGUAGE OverloadedStrings #-}
import Database.SQLite3
import Data.Text
cb :: ColumnCount -> [Text] -> [Maybe Text] -> IO ()
cb n cnl ct = do print $ cnl !! 1
return ()
main = do
dh <- open "fileinfo.sqlite"
execWithCallback dh "select * from files;" cb
close dh
but then, what is the point of the type??? And, how do I specify that cb is an ExecCallback??

In Haskell, with type you define a type synonym. In your example that means that ExecCallback is just an alias for the type ColumnCount -> [Text]-> [Maybe Text] -> IO (), they are interchangeable.
You could change the following lines
cb :: ColumnCount -> [Text] -> [Maybe Text] -> IO ()
cb n cnl ct = do print $ cnl !! 1
return ()
to
cb :: ExecCallback
cb n cnl ct = do print $ cnl !! 1
return ()
and everything would still work as is. It can make your code shorter and more readable.
One other good example is
type String = [Char]
in Prelude. I bet you normally use String instead of [Char] in most cases. But you're absolutely free to use either.
Another (completely unrelated) example is the conduit package where some type synonyms make a major difference:
type Sink i = ConduitM i Void
type Consumer i m r = forall o. ConduitM i o m r
For something that's a sink for values of any type i, Sink i seems way more readable than ConduitM i Void. Same for Consumer.

Related

Haskell: Pattern matching with named fields

I got ReaderT from Control.Monad.Reader:
newtype ReaderT r m a = ReaderT { runReaderT :: r -> m a }
and Action from Database.MongoDB.Query:
type Action = ReaderT MongoContext
Query functions of MongoDB are something like this:
delete :: MonadIO m => Selection -> Action m ()
I'm trying to use pattern mathing with Action m () to check if it is Action IO () or Action _ ()
A simple case like this
case x of
Action IO () -> True
Action _ () -> False
doesn't work, because Action is not a data constructor. Probably I should use something like this:
case x of
ReaderT MongoContext IO () -> True
ReaderT MongoContext _ () -> False
But then I get an error:
The constructor ‘ReaderT’ should have 1 argument, but has been given 3
In the pattern: ReaderT MongoContext IO ()
In a case alternative:
ReaderT MongoContext IO ()
Should I pass MongoContext -> IO () instead? I'm out of ideas, please help me with that expression. Thanks <3
IO is a type, you absolutely cannot case match against it, it only exists at compile time.
In general, if you have a type variable constrained by a type class, you can only call things supported by that type class. You cannot know which particular type it is unless the typeclass implements methods for inspecting it, like Typeable. Neither Monad nor MonadIO implement this kind of run-time type discrimination, so what you want is, by design, not possible.
Also note that, you don't need to know "which m" delete is, since it's specialized to whatever m that YOU want it to be, so long as it is an instance of MonadIO. You can simply declare deleteIO sel = delete sel :: Action IO ()
What are you actually trying to get done here?
As Steven Armstrong said, what you're trying to do is very weird, you cannot pattern match on IO because is an abstract data type (constructors aren't visible) and if I were you I would rethink what I'm trying to achieve. Having said that, Haskell still gives you a way of inspecting types at runtime using Typeable eg (inside a ghci session):
import Data.Typeable
import Control.Monad.Trans.Reader
type MyType = ReaderT String IO
f :: MyType ()
f = ReaderT $ \env -> putStrLn env
checkF :: Typeable a => MyType a -> Bool
checkF x = case show (typeOf x) of
"ReaderT * [Char] IO ()" -> True
_ -> False
-- checkF f => True

Is there any "standard" way to utilize the equivalence of Reader and a normal function?

I am writing a framework, where the main function asks user about the function of type a -> [b].
However, because that function can be quite complex, its implementation can often look like this:
fn a = extractPartOfAAndConvert a ++ extractAnotherPartofAAndConvert a
That's why I figured using Reader might be a nice, idiomatic idea to fight that. However, at the same time I realize that some people might not want to use a monad.
While experimenting, I've crafted this solution:
class Iso a b where
isoFrom :: a -> b
isoTo :: b -> a
instance Iso a a where
isoFrom = id
isoTo = id
instance Iso (a -> b) (Reader a b) where
isoFrom f = reader f
isoTo m = runReader m
Which in turn allows me to do:
testCallback :: MyState -> Callback -> MyState
testCallback myState cb = cb myState
-- The important signature
testCallbackGeneric :: Iso Callback a => MyState -> a -> MyState
testCallbackGeneric myState cb = (isoTo cb) myState
callbackFunction :: Callback
callbackFunction s = s + 10
callbackMonad :: Reader MyState MyState
callbackMonad = do
x <- ask
return $ x - 10
-----------
let myStateA = testCallback myState callbackFunction
-- let myStateB = testCallback myState callbackMonad -- won't work, obviously
let myStateC = testCallbackGeneric myState callbackFunction
let myStateD = testCallbackGeneric myState callbackMonad
However, I feel very much like I'm reinventing the wheel.
Is there a way to express the equivalence of Reader to easily write such generic functions without resorting to creating my own type class?
You can simply use the fact that the function monad (->) r already has an instance for MonadReader r defined in Control.Monad.Reader. You can write functions using just the MonadReader constraint and use them either as normal functions or in other ReaderT monads:
f :: MonadReader Int m => m Int
f = do
a <- ask
return $ 2 * a + 3 * a
normally :: Int
normally = f 1
-- normally == 5
readerly :: Reader Int Int
readerly = do
result <- f
return $ 2 * result
> runReader f 1
5
> runReader readerly 1
10

Can I ignore the type of Either Right if I'm ignoring the value?

I have an IO action that runs the following pattern three times in a row:
runAction :: IO a -> IO Bool
runAction action = do
result <- action
case result of
Right _ -> return True
_ -> return False
callingFunc :: IO Bool
callingFunc = do
resA <- runAction a
resB <- runAction b
resC <- runAction c
return (resA && resB && resC)
a :: IO (Either ByteString Integer)
b :: IO (Either ByteString ByteString)
c :: IO (Either ByteString Bool)
This works fine, but I'd like to eliminate some redundancy. This doesn't work because of the type of the Right side of Either:
{-# LANGUAGE OverloadedStrings #-}
import Control.Monad
import Data.ByteString.Char8 as BSC
runAction :: Bool -> IO (Either ByteString a) -> IO Bool
runAction prev action = do
result <- action
case result of
Right _ -> return prev
_ -> return False
actA :: IO (Either ByteString Integer)
actA = return (Right 1)
actB :: IO (Either ByteString Bool)
actB = return (Right True)
main :: IO ()
main = do
res <- foldM runAction True [actA, actB]
print res
Resulting error:
Actions.hs:25:38:
Couldn't match type ‘Bool’ with ‘Integer’
Expected type: IO (Either ByteString Integer)
Actual type: IO (Either ByteString Bool)
In the expression: actB
In the third argument of ‘foldM’, namely ‘[actA, actB]’
But I never actually look at the value. I just check if I got Right or not.
Is there any way for me to hide or ignore the type of the Right of Either? Is there a better or more idiomatic way to reduce or abstract this?
EDIT: Sorry, must have pasted an old copy of code. Updated.
Your problem comes from the types of actA and actB being in the same list. Lists in Haskell are homogenous, you can't mix elements of different types. actA and actB have explicitly different types, there's no possible way for the types to be unified. You can't have the type [Either a1 b1, Either a2 b2], this sort of thing just doesn't exist (without a lot of extensions and type system magic, anyway).

How to pass a field constructor parameter to a function?

1) I need to pass a field constructor parameter to a function. I made some tests but i was unable to do so. Is it possible? Otherwise, is it possible with lens package?
2) Is it possible in a MonadState to modify a field using modify? (I made a few attempts, but without success. For example: modify (second = "x") does not work.
import Control.Monad.State
data Test = Test {first :: Int, second :: String} deriving Show
dataTest = Test {first = 1, second = ""}
test1 = runStateT modif1 dataTest -- OK
test2 = runStateT (modif2 "!") dataTest -- OK
test3 = runStateT (modif3 second) dataTest -- WRONG
-- modif1 :: StateT Test IO ()
modif1 = do
st <- get
r <- lift getLine
put $ st {second = "x" ++ r}
-- modif2 :: String -> StateT Test IO ()
modif2 s = do
stat <- get
r <- lift getLine
put $ stat {second = "x" ++ r ++ s}
-- modif3 :: ???? -> StateT Test IO ()
modif3 fc = do
stat <- get
r <- lift getLine
put $ stat {fc = "x" ++ r}
-- When i try to load the module, this is the result:
-- ghc > Failed:
-- ProvaRecord.hs:33:16:`fc' is not a (visible) constructor field name
As you said, you're probably looking for lenses. A lens is a value that allows to read, set or modify a given field. Usually with Control.Lens, you define fields with underscores and you use makeLenses to create full-featured lenses.
There are many combinators that allow lenses to be used together within MonadState. In your case we can use %=, which in this case would be specialized to type
(MonadState s m) => Lens' s b -> (b -> b) -> m ()
which modifies a state value using a given lens and a function that operates on the inside value.
Your example could be rewritten using lenses as follows:
{-# LANGUAGE TemplateHaskell, RankNTypes #-}
import Control.Lens
import Control.Monad.State
data Test = Test { _first :: Int
, _second :: String
}
deriving Show
-- Generate `first` and `second` lenses.
$(makeLenses ''Test)
-- | An example of a universal function that modifies any lens.
-- It reads a string and appends it to the existing value.
modif :: Lens' a String -> StateT a IO ()
modif l = do
r <- lift getLine
l %= (++ r)
dataTest :: Test
dataTest = Test { _first = 1, _second = "" }
test :: IO Test
test = execStateT (modif second) dataTest

Type of return in do block

I am trying to understand Monads in Haskell and during my countless experiments with code I have encountered this thing:
f2 = do
return "da"
and the fact that it doesnt want to compile with huge error regarding type. I think the only important part is this:
No instance for (Monad m0) arising from a use of return'
The type variable `m0' is ambiguous
So then I have changed my code to:
f2 = do
return "da" :: IO [Char]
And it worked perfectly well. But when I have tried to mess up a bit and change the type to IO Int it was an error once again. So why the type is "ambiguous" when it actually isnt?
Also when I will add something before return like:
f2 = do
putStrLn "das"
return 2
Then I dont have to specify the type of return.
So can someone explain me what is going on really? Also why is return outputting "da" in the first case? Not da without ""?
First let's just point out that
do
return a
Is exactly the same as
return a
Now, the problem is that return has the type
return :: Monad m => a -> m a
And when you have a declaration like
foo = bar
where foo has no arguments haskell makes it "monomorphic". The result of this is that Haskell can't guess what m is and won't generalize it so you need an explicit type signature. The most general one is
f2 :: Monad m => m String
f2 = return "das"
But you could also use IO or any other monad
f2 :: IO String
Finally, in your last example, since you're returning 2, you'd have to give a type signature that indicates you're returning some sort of number, like
f2 :: IO Integer
This is known Monomorphism_restriction
Use signatures
f2 :: Monad m => m String
f2 = do
return "da"
or use language extension:
{-# LANGUAGE NoMonomorphismRestriction #-}
f2 = do
return "da"
to get valid code
When learning about monads it's helpful to expand them out manually yourself, for instance the simple example:
test0 :: IO String
test0 = do
a <- getLine
putStrLn a
return a
If we enable the language extension {-# LANGUAGE ScopedTypeVariables #-} then we can annotate each of the lines in the monad with it's explicit type which will show the type of the return block.
{-# LANGUAGE ScopedTypeVariables #-}
test1 :: IO String
test1 = do
a <- getLine :: IO String
putStrLn a :: IO ()
return a :: IO String
We can also annotate the explicit type of the left hand side pattern matching which "extracts" from the monad context on the right hand side.
test2 :: IO String
test2 = do
(a :: String) <- getLine :: IO String
(() :: ()) <- putStrLn a :: IO ()
return a :: IO String
We can even expand out the do-notation into its constituting parts:
test3 :: IO String
test3 = getLine >>=
(\a -> putStrLn a >>=
\() -> return a)
Hope that helps build your monad intuition.

Resources