[Haskell-cafe] Scala: Type synonyms for implicits?

Matt parsonsmatt at gmail.com
Sun Mar 18 23:56:46 UTC 2018


You might not encounter it, as ImplicitParams isn't common, but it has a
nice answer. Note that `HasCallStack` is implemented as an implicit
parameter: (?callstack :: CallStack).


{-# LANGUAGE TypeOperators, LambdaCase, RankNTypes #-}

import GHC.Stack

type a ?-> b = HasCallStack => a -> b

foo :: a ?-> a
foo x = x

map' :: (a ?-> b) -> [a] ?-> [b]
map' f = \case
  [] -> []
  (x:xs) -> f x : map f xs

ohno :: Int ?-> String
ohno 5 = error "Five is my least favorite number."
ohno x = show x

main = print $ map' ohno [1..10]

This has the result:

*Main> main
["1","2","3","4","*** Exception: Five is my least favorite number.
CallStack (from HasCallStack):
  error, called at /home/matt/impl.hs:16:10 in main:Main
  ohno, called at /home/matt/impl.hs:19:21 in main:Main
  f, called at /home/matt/impl.hs:13:23 in main:Main
  map', called at /home/matt/impl.hs:19:16 in main:Main




Matt Parsons

On Sun, Mar 18, 2018 at 5:05 PM, Thomas Jakway <tjakway at nyu.edu> wrote:

>
> Posting this here since some of you are Scala programmers:
> https://stackoverflow.com/questions/49353695/type-synonyms-for-implicits
>
> A type-level question you won't encounter in Haskell.
>
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20180318/967ca3c7/attachment.html>


More information about the Haskell-Cafe mailing list