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
from dataclasses import dataclass | |
from typing import Callable, Generic, TypeVar, Dict | |
T = TypeVar('T') | |
V = TypeVar('V') | |
R = TypeVar('R') | |
class Reader(Generic[R, T]): | |
def __init__(self, func: Callable[[R], T]): | |
self.func = func |
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
#include <stdlib.h> | |
#include <stdbool.h> | |
#include <stdio.h> | |
#include <string.h> | |
#include "JuniorLib.h" | |
#define eqT14 0 | |
#define numT14 1 | |
struct BoxedValue* fac(); |
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
#include <string.h> /* strcpy */ | |
#include <stdlib.h> /* malloc */ | |
#include <stdio.h> /* printf */ | |
#include "uthash.h" | |
struct closure { | |
void* fn; | |
struct BoxedValue** env; | |
}; |
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 UndecidableInstances #-} | |
{-# LANGUAGE DeriveFunctor #-} | |
module Main where | |
-- Fix point | |
fix :: ((a -> b) -> (a -> b)) -> (a -> b) | |
fix f = f (fix f) |
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 FlexibleContexts #-} | |
{-# LANGUAGE UndecidableInstances #-} | |
{-# LANGUAGE DeriveFunctor #-} | |
module LambdaLifting where | |
import Control.Monad.Trans.Reader | |
import Control.Monad.Trans.Writer | |
import Control.Monad.State hiding (fix) | |
import Data.Char |
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 DeriveFunctor#-} | |
module Main where | |
import Prelude hiding (takeWhile) | |
fix :: ((a -> b) -> a -> b) -> a -> b | |
fix f = f (fix f) | |
data Fix f = In { out :: f (Fix f) } |
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 DeriveFunctor#-} | |
module Main where | |
fix :: ((a -> b) -> a -> b) -> a -> b | |
fix f = f (fix f) | |
data Fix f = In { out :: f (Fix f) } | |
ana :: Functor f => (a -> f a) -> (a -> Fix f) -> a -> Fix f |
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 DeriveFunctor#-} | |
module Main where | |
fix :: ((a -> b) -> a -> b) -> a -> b | |
fix f = f (fix f) | |
data Fix f = In { out :: f (Fix f) } | |
ana :: Functor f => (a -> f a) -> (a -> Fix f) -> a -> Fix f |
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 DeriveFunctor#-} | |
module Main where | |
fix :: ((a -> b) -> a -> b) -> a -> b | |
fix f = f (fix f) | |
newtype Fix f = In { out :: f (Fix f) } | |
type Algebra f a = f a -> a |
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 DeriveFunctor#-} | |
module Main where | |
fix :: ((a -> b) -> a -> b) -> a -> b | |
fix f = f (fix f) | |
newtype Fix f = In { out :: f (Fix f) } | |
ana :: Functor f => (a -> f a) -> (a -> Fix f) -> a -> Fix f |
NewerOlder