Last active
April 27, 2021 01:03
-
-
Save puffnfresh/434fe3b06953845c4ee8daad11779bfd to your computer and use it in GitHub Desktop.
Writing functions once, using Cubix. FP.java, FP.py and FP.js are generated by running Main.hs
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
public class FP | |
{ | |
public static <A> A identity (A a) | |
{ | |
return a; | |
} | |
public static <A, B> A constant (A a, B b) | |
{ | |
return 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
function identity(a) { | |
return a; | |
} | |
function constant(a, b) { | |
return 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
def identity(a): | |
return a | |
def constant(a, b): | |
return 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 TypeOperators #-} | |
{-# LANGUAGE FlexibleContexts #-} | |
{-# LANGUAGE ConstraintKinds #-} | |
{-# LANGUAGE ScopedTypeVariables #-} | |
{-# LANGUAGE GADTs #-} | |
{-# LANGUAGE TypeSynonymInstances #-} | |
{-# LANGUAGE FlexibleInstances #-} | |
module Main where | |
import Cubix.Essentials | |
import Cubix.ParsePretty (RootSort) | |
import Cubix.Language.Parametric.Syntax | |
import qualified Cubix.Language.Java.Parametric.Common as J | |
import qualified Cubix.Language.JavaScript.Parametric.Common as JS | |
import qualified Cubix.Language.Python.Parametric.Common as P | |
class FunctionTypes fs where | |
functionParameter :: Term fs IdentL -> Term fs ParameterAttrsL | |
functionSignature :: [Term fs IdentL] -> Term fs IdentL -> Term fs FunctionDefAttrsL | |
javaRefType :: | |
( All HFunctor fs | |
, PairF :-<: fs | |
, ListF :-<: fs | |
, J.IdentIsIdent :-<: fs | |
, J.ClassType :-<: fs | |
, J.RefType :-<: fs | |
, J.Type :-<: fs | |
) => | |
Term fs IdentL -> | |
Term fs J.TypeL | |
javaRefType s = | |
J.iRefType (J.iClassRefType (J.iClassType (insertF [riPairF (J.iIdentIsIdent s) (insertF [])]))) | |
instance FunctionTypes MJavaSig where | |
functionParameter t = | |
J.iJavaParamAttrs (insertF []) (javaRefType t) 0 | |
functionSignature tps rt = | |
J.iJavaMethodDeclAttrs (insertF [J.iPublic, J.iStatic]) (insertF (tp <$> tps)) (insertF (Just (javaRefType rt))) (insertF []) | |
where | |
tp x = | |
J.iTypeParam (J.iIdentIsIdent x) (insertF []) | |
instance FunctionTypes MJSSig where | |
functionParameter _ = | |
iEmptyParameterAttrs | |
functionSignature _ _ = | |
iEmptyFunctionDefAttrs | |
instance FunctionTypes MPythonSig where | |
functionParameter _ = | |
P.iPyParamAttrs (insertF Nothing) (insertF Nothing) | |
functionSignature _ _ = | |
P.iPyFunDefAttrs (insertF Nothing) | |
class BlockBody fs where | |
blockBody :: Term fs BlockL -> Term fs FunctionBodyL | |
instance BlockBody MJavaSig where | |
blockBody = | |
J.iBlockIsFunctionBody | |
instance BlockBody MJSSig where | |
blockBody a = | |
JS.iJSBlockIsFunctionBody (JS.iBlockIsJSBlock a) | |
instance BlockBody MPythonSig where | |
blockBody a = | |
P.iPyBlockIsFunctionBody (P.iPyBlock (insertF Nothing) a) | |
class Return fs where | |
return' :: Term fs IdentL -> Term fs BlockItemL | |
instance Return MJavaSig where | |
return' a = | |
J.iReturn (insertF (Just (injF a))) | |
instance Return MJSSig where | |
return' a = | |
JS.iJSReturn JS.iJSNoAnnot (insertF (Just (JS.iIdentIsJSExpression a))) (JS.iJSSemi JS.iJSNoAnnot) | |
instance Return MPythonSig where | |
return' a = | |
P.iReturn (insertF (Just (injF a))) iUnitF | |
type PolymorphicFunction fs = | |
( All HFunctor fs | |
, ListF :-<: fs | |
, MaybeF :-<: fs | |
, Ident :-<: fs | |
, FunctionDef :-<: fs | |
, PositionalParameter :-<: fs | |
, Block :-<: fs | |
, EmptyBlockEnd :-<: fs | |
, FunctionTypes fs | |
, BlockBody fs | |
, Return fs | |
) | |
identity :: | |
forall fs l. | |
( PolymorphicFunction fs | |
, InjF fs FunctionDefL l | |
) => | |
Term fs l | |
identity = | |
iFunctionDef | |
(functionSignature [a'] a') | |
(iIdent "identity") | |
(insertF [iPositionalParameter (functionParameter a') a]) | |
(blockBody (iBlock (insertF [return' a]) iEmptyBlockEnd)) | |
where | |
a :: (InjF fs IdentL t) => Term fs t | |
a = | |
iIdent "a" | |
a' :: (InjF fs IdentL t) => Term fs t | |
a' = | |
iIdent "A" | |
constant :: | |
forall fs l. | |
( PolymorphicFunction fs | |
, InjF fs FunctionDefL l | |
) => | |
Term fs l | |
constant = | |
iFunctionDef | |
(functionSignature [a', b'] a') | |
(iIdent "constant") | |
(insertF [ | |
iPositionalParameter (functionParameter a') a, | |
iPositionalParameter (functionParameter b') b | |
]) | |
(blockBody (iBlock (insertF [return' a]) iEmptyBlockEnd)) | |
where | |
a :: (InjF fs IdentL t) => Term fs t | |
a = | |
iIdent "a" | |
b :: (InjF fs IdentL t) => Term fs t | |
b = | |
iIdent "b" | |
a' :: (InjF fs IdentL t) => Term fs t | |
a' = | |
iIdent "A" | |
b' :: (InjF fs IdentL t) => Term fs t | |
b' = | |
iIdent "B" | |
class Library fs where | |
library :: [Term fs FunctionDefL] -> Term fs (RootSort fs) | |
instance Library MJavaSig where | |
library fs = | |
J.iCompilationUnit (insertF Nothing) (insertF []) (insertF [J.iClassTypeDecl fp]) | |
where | |
fp = | |
J.iClassDecl (insertF [J.iPublic]) (iIdent "FP") (insertF []) (insertF Nothing) (insertF []) (J.iClassBody (insertF (J.iMemberDecl . J.iFunctionDefIsMemberDecl <$> fs))) | |
instance Library MJSSig where | |
library fs = | |
JS.iBlockWithPrelude [] (iBlock (insertF (JS.iFunctionDefIsJSStatement <$> fs)) iEmptyBlockEnd) | |
instance Library MPythonSig where | |
library fs = | |
P.iModule (insertF (P.iFunctionDefIsStatement <$> fs)) | |
functionalLibrary :: | |
( PolymorphicFunction fs | |
, Library fs | |
) => | |
Term fs (RootSort fs) | |
functionalLibrary = | |
library [identity, constant] | |
main :: IO () | |
main = do | |
writeFile "FP.java" (pretty (functionalLibrary :: Term MJavaSig J.CompilationUnitL)) | |
writeFile "FP.js" (pretty (functionalLibrary :: Term MJSSig JS.JSASTL)) | |
writeFile "FP.py" (pretty (functionalLibrary :: Term MPythonSig P.ModuleL)) |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment