Skip to content

Instantly share code, notes, and snippets.

@cheery
Last active August 20, 2020 19:15
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 cheery/112a74f59940a74a2201fe025a875a6e to your computer and use it in GitHub Desktop.
Save cheery/112a74f59940a74a2201fe025a875a6e to your computer and use it in GitHub Desktop.
Record experiments with Paluh
module Main where
import Prelude
import Effect (Effect)
import Data.Foldable (fold)
import TryPureScript (h1, h2, p, text, list, indent, link, render, code)
import Unsafe.Coerce (unsafeCoerce)
import Prim.RowList
import Prim.Row
import Prim.RowList (Cons,Nil) as RL
import Prim.TypeError (class Fail, Text)
import Type.Equality (class TypeEquals)
-- import Partial (unsafeCrashWith)
-- function first(x : string | number | boolean) : null
-- function second(x : string | number) : null
-- function third(x : {two : {third : boolean | number}} | number) : null
data UnionCons a b
data UnionNil
class Param a b where
coercion :: b -> a
class RecordParam (a :: RowList) (b :: RowList)
--deepCoerce :: a -> b
instance unionConsRecord :: (RowToList a c
, RowToList b d
, RecordParam c d
) => Param (UnionCons (Record a) xs) (Record b) where
coercion = unsafeCoerce -- <<< deepCoerce
else
--instance unionEverything :: TypeEquals b a => Param a b where
-- coercion = unsafeCoerce
--else
instance unionConsArray :: Param a b
=> Param (UnionCons (Array a) xs) (Array b) where
coercion = unsafeCoerce
else
instance unionConsMatch :: Param (UnionCons t xs) t where
coercion = unsafeCoerce
else
instance unionConsSkip :: Param xs u => Param (UnionCons t xs) u where
coercion = unsafeCoerce
else
instance unionRecord :: (RowToList a c, RowToList b d, RecordParam c d)
=> Param (Record a) (Record b) where
coercion = unsafeCoerce -- <<< deepCoerce
--else
-- instance unionError :: Fail (Text "ok") => Param a b where
-- coercion = unsafeCoerce -- unsafeCrashWith "nope"
else
instance unionSame :: Param a a where
coercion = unsafeCoerce
else
instance unionVoid :: (TypeEquals y Void) => Param x y where
coercion = unsafeCoerce
instance recordParamCons :: (Param t u, RecordParam xs ys)
=> RecordParam (RL.Cons name t xs) (RL.Cons name u ys)
else
instance recordParamNil :: RecordParam (RL.Nil) (RL.Nil)
type Undefined = UnionCons String
(UnionCons Number
(UnionCons Boolean UnionNil))
type Undefined3 = UnionCons {two :: {
third :: UnionCons Boolean
(UnionCons Number UnionNil) }}
(UnionCons Number UnionNil)
type Undefined4 = UnionCons (Array Number)
(UnionCons Number UnionNil)
foreign import first :: Undefined -> Unit
first' :: forall a. Param Undefined a => a -> Unit
first' = first <<< coercion
test_first = first' true
foreign import third :: Undefined3 -> Unit
third' :: forall a. Param Undefined3 a => a -> Unit
third' = third <<< coercion
foreign import fourth :: Undefined4 -> Unit
fourth' :: forall a. Param Undefined4 a => a -> Unit
fourth' = fourth <<< coercion
test_third = third' 4.3
test_third2 = third' {two : {third : true}}
test_third3 = third' {two : {third : 3.2}}
-- test_third4 = third' {two : {third : "foo"}}
test_fourth = fourth' []
--foreign import data Undefined :: Type
--foreign import data Undefined2 :: Type
--foreign import undef :: Undefined
--foreign import first :: Undefined -> Unit
--foreign import second :: Undefined2 -> Unit
--fromString :: String -> Undefined
--fromString = unsafeCoerce
--fromNumber :: Number -> Undefined
--fromNumber = unsafeCoerce
class Cls x y | x -> y where
foo :: y → x
bar :: x → y → x
instance clsStringInt :: Cls String Int where
foo = show
bar x y = x <> foo y
-- instance clsStringNumber :: Cls String Number where
-- foo = show
-- bar x y = x <> foo y
instance clsNumberNumber :: Cls Number Number where
foo x = x
bar x y = x + y
class Q x
class R x y | x -> y
instance r0 :: R Int String
else instance r1 :: Q a => R Number a
else instance r2 :: R String (Array Int)
else instance r3 :: R a (Array Int)
class SomeClass t
instance thisInstance :: SomeClass String
else instance thatInstance :: SomeClass a
class F t u | t -> u
instance fInt :: F Int String
else instance fString :: F String String
else instance fAnything :: F a String
main :: Effect Unit
main =
render $ fold
[ h1 (text "Try PureScript!")
, p (text "Try out the examples below, or create your own!")
, h2 (text "Examples")
, list (map fromExample examples)
, h2 (text "Share Your Code")
, p (text "Code can be loaded from a GitHub Gist. To share code, simply include the Gist ID in the URL as follows:")
, indent (p (code (text " try.purescript.org?gist=gist-id")))
, p (fold
[ text "The Gist should contain a file named "
, code (text "Main.purs")
, text " containing your PureScript code."
])
]
where
fromExample { title, gist } =
link ("https://gist.github.com/" <> gist) (text title)
examples =
[ { title: "Algebraic Data Types"
, gist: "387999a4467a39744ece236e69a442ec"
}
, { title: "Loops"
, gist: "429eab1e957e807f9feeddbf4f573dd0"
}
, { title: "Operators"
, gist: "8395d2b421a5ca6d1056e301a6e12599"
}
, { title: "Records"
, gist: "170c3ca22f0141ed06a120a12b8243af"
}
, { title: "Recursion"
, gist: "659ae8a085f1cf6e52fed2c35ad93643"
}
, { title: "Do Notation"
, gist: "525cb36c147d3497f652028db1214ec8"
}
, { title: "Type Classes"
, gist: "b04463fd49cd4d7d385941b3b2fa226a"
}
, { title: "Generic Programming"
, gist: "e3b6284959f65ac674d39aa981fcb8fb"
}
, { title: "QuickCheck"
, gist: "69f7f94fe4ff3bd47f4b"
}
]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment