Skip to content

Instantly share code, notes, and snippets.

@safareli
Created October 8, 2018 15:25
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save safareli/edd342da6b16f05df8257a71990e96a0 to your computer and use it in GitHub Desktop.
Save safareli/edd342da6b16f05df8257a71990e96a0 to your computer and use it in GitHub Desktop.
Example of Data.Exists like encoding of existentials with TypeClass constraints
"use strict";
var Control_Category = require("../Control.Category");
var Data_Foldable = require("../Data.Foldable");
var Data_Monoid = require("../Data.Monoid");
var Prelude = require("../Prelude");
var Unsafe_Coerce = require("../Unsafe.Coerce");
var runFoldableExists = function (f) {
return function (e) {
return e(function (dictFoldable) {
return f(dictFoldable);
});
};
};
var y = runFoldableExists(function (dictFoldable) {
return function (z1) {
return Data_Foldable.foldMap(dictFoldable)(Data_Monoid.monoidString)(Control_Category.id(Control_Category.categoryFn))(z1);
};
});
var mkFoldableExists = function (dictFoldable) {
return function (x1) {
var g = function (f) {
return f(dictFoldable)(x1);
};
return g;
};
};
var x = mkFoldableExists(Data_Foldable.foldableArray)([ "foo", "bar" ]);
var z = y(x);
module.exports = {
mkFoldableExists: mkFoldableExists,
runFoldableExists: runFoldableExists,
x: x,
y: y,
z: z
};
module Foo where
import Prelude
import Unsafe.Coerce (unsafeCoerce)
import Data.Foldable (class Foldable, foldMap)
foreign import data FoldableExists :: Type -> Type
type OnFoldableExists f a r = Foldable f => f a -> r
mkFoldableExists
:: forall f a
. OnFoldableExists f a (FoldableExists a)
mkFoldableExists x = unsafeCoerce g
where
g :: forall r. OnFoldableExists f a r -> r
g f = f x
runFoldableExists
:: forall a r
. (forall f. OnFoldableExists f a r)
-> FoldableExists a
-> r
runFoldableExists f e = e' f
where
e' :: (forall f. OnFoldableExists f a r) -> r
e' = unsafeCoerce e
x :: FoldableExists String
x = mkFoldableExists ["foo","bar"]
y :: FoldableExists String -> String
y = runFoldableExists \z -> foldMap id z
z :: String
z = y x -- "foobar"
"use strict";
var Data_Foldable = require("../Data.Foldable");
var Data_Monoid = require("../Data.Monoid");
var Data_Show = require("../Data.Show");
var Prelude = require("../Prelude");
var Unsafe_Coerce = require("../Unsafe.Coerce");
var runFoldableShowExists = function (f) {
return function (e) {
return e(function (dictFoldable) {
return function (dictShow) {
return f(dictFoldable)(dictShow);
};
});
};
};
var y = runFoldableShowExists(function (dictFoldable) {
return function (dictShow) {
return function (z1) {
return Data_Foldable.foldMap(dictFoldable)(Data_Monoid.monoidString)(Data_Show.show(dictShow))(z1);
};
};
});
var mkFoldableShowExists = function (dictFoldable) {
return function (dictShow) {
return function (x1) {
var g = function (f) {
return f(dictFoldable)(dictShow)(x1);
};
return g;
};
};
};
var x = mkFoldableShowExists(Data_Foldable.foldableArray)(Data_Show.showInt)([ 1, 2 ]);
var z = y(x);
module.exports = {
mkFoldableShowExists: mkFoldableShowExists,
runFoldableShowExists: runFoldableShowExists,
x: x,
y: y,
z: z
};
module FoldableShowExists where
import Prelude
import Unsafe.Coerce (unsafeCoerce)
import Data.Foldable (class Foldable, foldMap)
foreign import data FoldableShowExists :: Type
type OnFoldableShowExists f a r = Foldable f => Show a => f a -> r
mkFoldableShowExists
:: forall f a
. OnFoldableShowExists f a FoldableShowExists
mkFoldableShowExists x = unsafeCoerce g
where
g :: forall r. OnFoldableShowExists f a r -> r
g f = f x
runFoldableShowExists
:: forall r
. (forall f a. OnFoldableShowExists f a r)
-> FoldableShowExists
-> r
runFoldableShowExists f e = e' f
where
e' :: (forall f a. OnFoldableShowExists f a r) -> r
e' = unsafeCoerce e
x :: FoldableShowExists
x = mkFoldableShowExists [1, 2]
y :: FoldableShowExists -> String
y = runFoldableShowExists \z -> foldMap show z
z :: String
z = y x -- "12"
@safareli
Copy link
Author

safareli commented Oct 8, 2018

This is better version as you don't need unsafeCoerce

module Main where

import Prelude
import Data.Foldable

newtype FoldableBox a = FoldableBox (forall r. (forall f. Foldable f => f a -> r) -> r)

mkFoldableBox :: forall f a. Foldable f => f a -> FoldableBox a
mkFoldableBox a = FoldableBox \k -> k a

runFoldableBox :: forall a r. (forall f. Foldable f => f a -> r) -> FoldableBox a -> r
runFoldableBox k1 (FoldableBox k2) = k2 k1

foo :: FoldableBox Int
foo = mkFoldableBox [1, 2, 3]

test :: Int
test = foo # runFoldableBox sum

source https://gist.github.com/natefaubion/d33aa875fa5c98178df159091fd4f348

@safareli
Copy link
Author

safareli commented Oct 8, 2018

nested forall can be used for describing Data.Exists but with cost of extra heap allocation

data StreamF a s = StreamF s (s -> Tuple s a)
type Stream a = Exists (StreamF a)

newtype Exists f = Exists (forall r. (forall a. f a -> r) -> r)

mkExists :: forall f a. f a -> Exists f
mkExists a = Exists \k -> k a

runExists :: forall f r. (forall a. f a -> r) -> Exists f -> r
runExists k1 (Exists k2) = k2 k1

squares :: Int -> Stream Int
squares i = mkExists $ StreamF i \s -> Tuple (s*s) s

next :: forall a. Stream a -> Stream a
next = runExists \(StreamF s f) -> mkExists $ StreamF (fst $ f s) f

head :: forall a. Stream a -> a
head = runExists \(StreamF s f) -> snd $ f s

test :: Int
test = head $ next $ next $ squares 2 -- test == 16

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment