Giter Club home page Giter Club logo

Comments (8)

mgsloan avatar mgsloan commented on September 6, 2024

It would be nice if Display had an arbitrary reader-like environment.

I've also wanted this in the past for things like aeson instances - I think it's a good general pattern for these sorts of instances. For example, lets say you have an instance for serializing DB keys to the client, and there's some other identifier that's used for the client. You could have a Map DbKey ClientKey in the environment, and access it.

So, for Display this would look like

class Display e a where
  display :: e -> a -> DisplayBuilder

Lets say you had a different display for debugging vs users. Using the environment for this might look like

data Audience = Programmer | User

class HasAudience e where
  getAudience :: e -> Audience

instance HasAudience e => Display e AnExceptionOrSomething where
  display e x = case getAudience e of
    Programmer -> displayShow x
    User -> case x of ...

I haven't thought this through much, but it could make sense to have a monadic API. Something along the lines of display :: a -> ReaderT e (Writer DisplayBuilder)

from rio.

akhra avatar akhra commented on September 6, 2024

+1 to @mgsloan's idea. At this very moment my to-do list includes a custom ToJSON instance to remove the initial capital from an enum value. It would be great to have a consistent way of handling this sort of thing, rather than dealing with it ad-hoc and piecemeal.

Bikeshed: Display c a, for context. e is standard for error, overloading it with environment introduces mental load to disambiguate. Alternately, being a little more verbose is fine: Display env a

from rio.

akhra avatar akhra commented on September 6, 2024

Hmm... wouldn't this also work, with the same class definition?

instance Display 'Programmer a where
  display = displayShow

instance Display 'User a where
  display = \case ...

Seems like that would make it much more convenient to use without a monadic context.

Edit: My bad, the argument counts don't match... I was thinking this could be done just with TypeApplication but it would at the very least require a Proxy to be used with the same Reader-friendly definition. (And I don't even know if you can Proxy @'User? Never seen it.) Still, I feel like this is a good direction overall.

from rio.

mgsloan avatar mgsloan commented on September 6, 2024

You could, but I would want to have arbitrary data in the context. Note that such a context need not be monadic, I was just considering that do notation could be nice for this.

There could be some benefits to having it as a type parameter. In particular, you might want to declare that there is only a Programmer-oriented display for a type. For convenience, could have this be implied by the context type:

type family DisplayAudience (c :: *) :: Audience

display :: forall t c a. (t ~ DisplayAudience c) => c -> a -> DisplayBuilder
display = displayImpl (Proxy :: Proxy t)

class Display t c a where
  displayImpl :: Proxy t -> c -> a -> DisplayBuilder

instance Display 'Programmer c AnExceptionOrSomething where
  displayImpl = displayShow

instance Display 'User c AnExceptionOrSomething where
  displayImpl = \case ...

instance Display 'Programmer c InternalThing where
  displayImpl = displayShow

Then again, it may not be so good to bake such fanciness into something that people learning Haskell would run into early..

from rio.

chrisdone avatar chrisdone commented on September 6, 2024

I understand the need for additional parameters when printing, such as in the Map DbKey ClientKey, but I do feel like this complicates matters.

Display (human) was originally conceived as counterpart to Show (programmer). I feel that just having two classes is fine. A separate class for JSON, debugging, serialization, displaying is the usual way. We don't need to put the kitchen-sink in one class.

Regarding the additional parameter to Display, I definitely see the use-case for it (holding e.g. mappings, current indentation, etc.). Going back to the first proposal:

class Display e a where
  display :: e -> a -> DisplayBuilder

This is handy for us writing instances, but it does add some burden of having to add an extra parameter to every call to display. Changing to a monad is another way of doing it. Or just putting it in DisplayBuilder r and then you can still do x <> y.

We should also include in this discussion the reflection package, for example Display e a is a specialization of the more general Tagged type (see below), which can be applied to any class instance when needed. This is more advanced than including an additional parameter, but more general. If we're worried about up-front burden, this is the only option so far that requires no burden for newbies to just use the Display class.

{-# LANGUAGE FlexibleInstances, TypeApplications, UndecidableInstances, ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
import           Data.Tagged
import qualified Data.ByteString.Lazy as L
import           Data.String
import           Data.Proxy
import qualified Data.Map.Strict as M
import           Data.Map.Strict (Map)
import           Data.ByteString.Builder
import           Data.List
import           Data.Monoid
import           Data.Reflection

class Display a where display :: a -> Builder

data Type = IntType | StringType

instance Display Type where
  display IntType = "Int"
  display StringType = "String"

data TypeError = TypeMismatch Type Type [TypeError]

instance Reifies s (Map String Type) => Display (Tagged s TypeError) where
  display (Tagged (TypeMismatch t1 t2 otherErrors)) =
    "Couldn't match " <> display t1 <> " against " <> display t2 <>
    "\nContext:\n" <>
    mconcat
      (intersperse
         "\n"
         (map
            (\(k, v) -> fromString k <> " :: " <> display v)
            (M.toList (reflect (Proxy @s))))) <> 
    "\nOther errors:\n" <> 
    mconcat (intersperse "\n" (map (display . tagWith (Proxy @s)) otherErrors))

main :: IO ()
main =
  L.putStr
    (toLazyByteString
       (reify
          (M.fromList [("x", IntType)])
          (\s ->
             display
               (tagWith
                  s
                  (TypeMismatch
                     IntType
                     StringType
                     [TypeMismatch StringType IntType []])))))

from rio.

snoyberg avatar snoyberg commented on September 6, 2024

I've fixed naming and added some missing instances. I think that's all we need to do for now, closing.

from rio.

roman avatar roman commented on September 6, 2024

I would like to re-explore @mgsloan comment in regards to having a Display typeclass that has multiple variants. Many times I would like to have a Pretty Print version or a JSON version of a record depending on context, and I would love this functionality to be specified at call time.

I'm thinking; we would have a group of standard contexts that make sense (e.g., Pretty, Show, JSON, etc.)

Has this idea already been scratched altogether? cc: @snoyberg @chrisdone

from rio.

akhra avatar akhra commented on September 6, 2024

I started looking at this a week or so ago. It feels like it should boil down to:

type family DisplayContext ctx

class (DisplayContext ctx) => Display' ctx a where
  display' :: a -> DisplayContext ctx

data DisplayContextDefault
type instance DisplayContext DisplayContextDefault = Utf8Builder
type Display = Display' DisplayContextDefault

Except that of course this doesn't work; DisplayContext ctx is not a constraint, and everything else I've tried so far has some other issue with type resolution.

nb: It works fine if there's no indirection on the output type (i.e. class Convert a b where convert :: a -> b) but that seems... dangerous.

from rio.

Related Issues (20)

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.