Search code examples
debugginghaskelltypesghcconcrete

haskell -- is -ddump-simpl the best way to get a concrete type?


I had previously written a function that seems to work, but unfortunately I didn't write the code very nicely, and now have to figure it out again [that I'm modifying the monad transformer stack I'm working with].

run_astvn ::
    LowerMonadT (StateT LowerSketchData Identity) β
    -> Seq SketchAST
run_astvn x = get_ast2 $ runIdentity $
    runStateT (runStateT (runStateT x empty) empty)
        (LowerSketchData Set.empty)
    where get_ast2 = snd . fst

I want to get the concrete type of get_ast2. I seem to be able to add the flag -ddump-simpl and grep through my terminal output until I find, (cleaned up a little)

(((β, Seq SketchAST), Seq SketchAST), LowerSketchData) -> Seq SketchAST

(Sorry this is likely nonsense to everyone else, but the point is it is useful for me.) Is there a faster / more convenient way to do this? In case it's not obvious, what I mean by "concrete" in this case is that the above type is useful; knowing the type of snd . fst is not :).


Solution

  • There's two ways I know of to do this currently, and they're both sort of hacks. The first is to use implicit parameters:

    {-# LANGUAGE ImplicitParams #-}
    import Control.Monad.State
    import Control.Monad.Identity
    import Data.Sequence
    import qualified Data.Set as Set
    
    data LowerSketchData = LowerSketchData (Set.Set Int)
    type LowerMonadT m = StateT (Seq SketchAST) (StateT (Seq SketchAST) m)
    data SketchAST = SketchAST
    
    --run_astvn ::
    --    LowerMonadT (StateT LowerSketchData Identity) β
    --    -> Seq SketchAST
    run_astvn x = ?get_ast2 $ runIdentity $
        runStateT (runStateT (runStateT x empty) empty)
            (LowerSketchData Set.empty)
    --    where get_ast2 = snd . fst
    

    Then, in ghci:

    *Main> :t run_astvn
    run_astvn
      :: (?get_ast2::(((a, Seq a1), Seq a2), LowerSketchData) -> t) =>
         StateT
           (Seq a1) (StateT (Seq a2) (StateT LowerSketchData Identity)) a
         -> t
    

    The other way is to give an intentionally wrong type signature and check how the compiler complains.

    import Control.Monad.State
    import Control.Monad.Identity
    import Data.Sequence
    import qualified Data.Set as Set
    
    data LowerSketchData = LowerSketchData (Set.Set Int)
    type LowerMonadT m = StateT (Seq SketchAST) (StateT (Seq SketchAST) m)
    data SketchAST = SketchAST
    
    run_astvn ::
        LowerMonadT (StateT LowerSketchData Identity) β
        -> Seq SketchAST
    run_astvn x = get_ast2 $ runIdentity $
        runStateT (runStateT (runStateT x empty) empty)
            (LowerSketchData Set.empty)
    --    where get_ast2 = snd . fst
        where get_ast2 :: (); get_ast2 = undefined
    

    This gives the error:

    test.hs:13:19:
        The first argument of ($) takes one argument,
        but its type `()' has none
        In the expression:
          <snip>
    

    Changing the wrong type to () -> ():

    test.hs:13:30:
        Couldn't match expected type `()'
                    with actual type `(((β, Seq SketchAST), Seq SketchAST),
                                       LowerSketchData)'
        In the second argument of `($)', namely
          <snip>
    

    So now we know the type should look like (((β, Seq SketchAST), Seq SketchAST), LowerSketchData) -> (). One last iteration gets rid of the final (), because the compiler complains that:

    test.hs:13:19:
        Couldn't match expected type `Seq SketchAST' with actual type `()'
        In the expression:
          <snip>
    

    ...so the other () should be Seq SketchAST.