Skip to content

Instantly share code, notes, and snippets.

View Elvecent's full-sized avatar

Kirill Valiavin Elvecent

View GitHub Profile
@Elvecent
Elvecent / App.tsx
Last active October 28, 2019 11:38
Nice React counter
import { createContext, useContext, useReducer } from "react";
import * as React from "react";
import { render } from "react-dom";
// <LibraryCode>
const StateContext: React.Context<[any, React.Dispatch<any>]> = createContext(
undefined
);
function StateProvider<S, A>({
@Elvecent
Elvecent / Pure.hs
Created September 11, 2019 12:14
Deep Pure Fun
{-# LANGUAGE TypeApplications, DataKinds, KindSignatures, TypeFamilies, MultiParamTypeClasses, FunctionalDependencies, UndecidableInstances #-}
module Main where
import Data.Functor.Compose
import Data.Functor.Identity
import Data.Coerce
data Nat = Zero | Succ Nat
@Elvecent
Elvecent / Concurrent.hs
Last active September 1, 2019 23:52
Running jobs asynchronously but yielding results in order
module Utils.Concurrent (mkPipeline, launchNukes) where
import Control.Concurrent (threadDelay)
import Control.Concurrent.Async (Async, async, cancel, wait)
import Control.Concurrent.STM (TBQueue, atomically, newTBQueueIO,
readTBQueue, writeTBQueue)
import Control.Monad (forever, void)
import Control.Monad.IO.Class (MonadIO, liftIO)
import GHC.Natural (Natural)
@Elvecent
Elvecent / Main.hs
Last active September 14, 2019 10:46
Free Monad & Cofree Comonad
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeSynonymInstances #-}
module Main where
@Elvecent
Elvecent / Main.hs
Created August 15, 2019 20:08
Cool coroutines with free monad transformers
-- packages "free" and "transformers" assumed
{-# LANGUAGE DeriveFunctor #-}
module Main where
import Control.Monad.Trans.Free
import Control.Monad.Trans.Class
data CoroutineF a = Yield a
@Elvecent
Elvecent / Parser.hs
Last active May 19, 2019 08:31
Monadic parsers
{-# Language DeriveFunctor #-}
module Parser where
newtype Parser a = Parser { parse :: String -> [(a, String)] }
deriving Functor
parserBind :: Parser a -> (a -> Parser b) -> Parser b
parserBind (Parser p) mf = Parser $ \s ->
p s >>= (\(x,s) -> parse (mf x) s)
@Elvecent
Elvecent / Bubble.dart
Last active February 2, 2023 13:25
Dart/Flutter dialog imitation with streams
import 'package:flutter/material.dart';
import 'func.dart';
class Message {
Message(this.text, this.isMe);
String text;
bool isMe;
}
@Elvecent
Elvecent / haskell.md
Last active January 14, 2020 10:00
Minimal Haskell Emacs

Minimal Haskell Emacs configuration, from scratch

This little instruction shows how to set up Emacs with some packages to start writing Haskell in a more or less convenient way (including, but not limited to: smart auto completion, type info, autoformatting).

Get emacs

First step: get Emacs for your platform. This should be simple.

Find your init file

That's usually ~/.emacs on unix-like systems. ~ stands for "home folder" and on Windows it's usually AppData\Roaming. Check this out.

Set up MELPA

@Elvecent
Elvecent / Expr.hs
Created December 28, 2018 15:10
Expressions...
{-# Language GADTs,
DataKinds,
KindSignatures,
StandaloneDeriving,
DeriveFunctor,
TypeFamilies
#-}
import Data.Function
@Elvecent
Elvecent / Main.hs
Last active November 28, 2018 09:01
An example on typesafe field validation in Haskell with basic type-level hackery.
{-# Language TypeSynonymInstances
, FlexibleInstances
, MultiParamTypeClasses
, KindSignatures
, GADTs
, DataKinds
, TypeFamilies
, AllowAmbiguousTypes
, TypeApplications
#-}