Created
February 5, 2019 13:54
-
-
Save i-am-tom/e5f9c36b0f76e89437a51c6156f7555c to your computer and use it in GitHub Desktop.
JavaScript.method(... xs)
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE DataKinds #-} | |
{-# LANGUAGE FlexibleInstances #-} | |
{-# LANGUAGE LambdaCase #-} | |
{-# LANGUAGE FunctionalDependencies #-} | |
{-# LANGUAGE TypeFamilies #-} | |
{-# LANGUAGE TypeOperators #-} | |
{-# LANGUAGE UndecidableInstances #-} | |
module Main where | |
import Data.Kind | |
import GHC.TypeLits | |
-- | Being a bit silly, perhaps: let's imagine we have a function like | |
-- @(==) :: a -> a -> Bool@, and we have a /list/ of its arguments, @[a]@. | |
-- Let's write a function that allows us to go from @a -> a -> ... -> r@ to | |
-- @[a] -> Maybe r@. For example: | |
eg0 :: Maybe Int | |
eg0 = listify (+) [1, 2] -- Just 3 | |
eg1 :: Maybe String | |
eg1 = listify [] "hello" -- Just "hello" | |
eg2 :: Maybe Int | |
eg2 = listify (+) [1] -- Nothing | |
-- We'll need to know what the expected output of the function is, as well as | |
-- the arguments' shared type. We'll call the whole function @input@, the | |
-- result @output@, and the type of all the arguments @element@. Note the | |
-- functional dependency says that we can look at the input function, and | |
-- always know its output (HINT: it's the thing at the end!) | |
class Listable input element output | input -> output where | |
listify :: input -> [element] -> Maybe output | |
-- f ^ args ^ result ^ | |
-- If we have a function of any sort, we require that the argument's type is | |
-- the same as our @element@ type, and the "result" of the function is also | |
-- 'Listable'. Note here we use @head ~ element@ rather than just having a head | |
-- of @Listable (element -> input) element output@ because this allows the | |
-- function to work even in polymorphic cases. If you're interested to see | |
-- more, remove the constraint and see how it affects the examples' | |
-- type-checking! | |
instance (head ~ element, Listable input element output) | |
=> Listable (head -> input) element output where | |
listify f = \case | |
[ ] -> Nothing -- We've run out of arguments to pass in! | |
x : xs -> listify (f x) xs | |
-- If we /definitely don't/ have a function, we're done and we can return | |
-- 'Just' the input as the output! This is like composing 'id' - it won't | |
-- change the behaviour of our function, but it's a nice "base case". | |
-- | |
-- Note the use once more of the equality constraint: if we /don't/ have a | |
-- function, we can match on any output and /then/ constrain it to be the same | |
-- as the input. This is, once more, for the sake of polymorphism: try removing | |
-- the type signatures from the examples, removing the equality constraint, and | |
-- changing the head to @Listable input element input@! | |
-- | |
-- Note also the @INCOHERENT@ pragma. We want to make sure that we /only/ pick | |
-- this instance if we're not dealing with a function: this is the "back up" | |
-- instance. I encourage you to try @OVERLAPPABLE@ and see the problem remain: | |
-- we don't /know/ that this instance is less specific than the above instance | |
-- unless we know whether we have a function or not, so @OVERLAPPABLE@ isn't | |
-- really a strong enough claim. @INCOHERENT@, however, says "ignore me unless | |
-- you have absolutely no other option", and thus does what we want! | |
instance {-# INCOHERENT #-} (input ~ output) | |
=> Listable input element output where | |
listify x _ = Just x |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment