Monadless do-blocks - Haskell

Welcome to the Functional Programming Zulip Chat Archive. You can join the chat here.

Georgi Lyubenov // googleson78

Ok so

f :: String
f = do
  "lol"

this is fine, and looks pretty normal to me

Georgi Lyubenov // googleson78

but also...

f :: String
f = do
  _ <- pure "heha"
  "lol"

this works

Georgi Lyubenov // googleson78

what does the pure "haha" + the bind desugar to??

Georgi Lyubenov // googleson78

I can tell for sure that it's not ignored, because..

Georgi Lyubenov // googleson78
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TypeFamilies #-}

type family B (b :: Bool)

type instance B True = ()

type instance B False = ()

data Dict c where
  Dict :: c => Dict c

data SBool (b :: Bool) where
  STrue :: SBool True
  SFalse :: SBool False

bla :: SBool b -> Dict (Show (B b))
bla STrue = Dict
bla SFalse = Dict

f :: SBool b -> B b -> String
f sb bb = do
  Dict <- pure $ bla sb
  show bb
Georgi Lyubenov // googleson78

so I guess it has to be some case statement??

Georgi Lyubenov // googleson78

in any case, very weird that they decided to do that.. I think?

Georgi Lyubenov // googleson78

but it might just be useful for my use case now :smiling_imp:

Georgi Lyubenov // googleson78

or are these the evil machinations of some weird Monad instance? (like (r->))

TheMatten

:joy: - I was confused too, so I plugged it into -ddump-ds and of course, GHC.Base.$fMonad[] appeared :big_smile:

TheMatten

Easy to forget for sure :big_smile:

Georgi Lyubenov // googleson78

bye bye easy introduction of Dicts :sob:

Georgi Lyubenov // googleson78

is there some "cleaner" way to introduce constraints, than to do with* style functions, that increase indentation levels (depending on your formatting style)

Georgi Lyubenov // googleson78

or in general is there some cleaner way to handle producing constraints for instances for type families? :(

Georgi Lyubenov // googleson78

TheMatten said:

:joy: - I was confused too, so I plugged it into -ddump-ds and of course, GHC.Base.$fMonad[] appeared :big_smile:

btw if you're running hls, you can ask for the type of pure above and it will also show you the concrete type being used at that point, not only the generic type it has

TheMatten

Just do

module Do.Identity where
  (>>=) = (&)
  (>>) = const
  pure = id
{-# language QualifiedDo #-}
import Do.Identity qualified as I

f sb bb = I.do
  Dict <- bla sb
  show bb

:big_smile:

Georgi Lyubenov // googleson78

but I'm not on a ghc supporting it yet

Georgi Lyubenov // googleson78

lovely how many good things come out of just QualifiedDo

TheMatten

It's how all sugar should work IMHO :smile:

Georgi Lyubenov // googleson78

at this point I'm just sticking all of them in a single type Shows ty = <list all the Shows I need> and having a hasShow :: Sing ty -> (Shows ty => r) -> r

Georgi Lyubenov // googleson78

but this doesn't scale well when not all your datatypes are in one place

Georgi Lyubenov // googleson78

I guess the ""solution"" to this is to create a unifying module for all of them which only has Shows and hasShow in it

Georgi Lyubenov // googleson78

I wonder how much this makes ghc slower

Georgi Lyubenov // googleson78

it also doesn't scale well if you have more tys

bradrn

Quick question: I’ve been reading through this thread, and there’s a couple of references to GHC.Base.$fMonad[] as an explanation for how this works. As someone who is unfamiliar with the internals of GHC, what does GHC.Base.$fMonad[] do and why is it relevant here?

Georgi Lyubenov // googleson78

I think that's the internal name for the dict for the Monad instance for []

Georgi Lyubenov // googleson78

do you know how type classes are handled in core?

TheMatten

@bradrn

GHC translates classes into what are basically record types - so

class Applicative m => Monad m where
  return :: a -> m a
  (>>=)  :: m a -> (a -> m b) -> m b
  (>>)   :: m a -> m b -> m b

translates into something equivalent to

data Monad m = Monad{
    applicative :: Applicative m
  , return      :: forall a. a -> m a
  , ...
  }

Instances are then represented simply as values of this datatype - or functions, if they take some constraints
Finally, $fMonad[] is simply some generated name given to one such instance (Monad [])

TheMatten

It isn't really about typeclass desugaring in this case - I just dumped desugared internal representation of Haskell, because I wanted to see what do turns into :smile:

Georgi Lyubenov // googleson78

I think it has almost the same role as a vtable

TheMatten

Yeah - compared to OOP languages, Haskell basically decouples vtables into separate entities (constraints), instead of packing them together with defined datatype

bradrn

Ah, of course! So that do block just ends up using the Monad [] instance. Thanks @Georgi Lyubenov // googleson78 @TheMatten!