Skip to content

Instantly share code, notes, and snippets.

View cblp's full-sized avatar

Yuriy Syrovetskiy cblp

  • Montenegro
View GitHub Profile
#include <iostream>
using namespace std;
struct Point {
double x, y;
};
string to_string(Point p) {
return string("Point{") + to_string(p.x) + ", " + to_string(p.y) + "}";
}
@cblp
cblp / DLList.hs
Created June 9, 2017 16:00
Doubly-linked list in Haskell, using IORefs
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}
import Data.IORef
type ItemPtr a = IORef (Maybe (Item a))
data Item a = Item{value :: a, prev, next :: !(ItemPtr a)}
newtype DLList a = DLList (IORef (Maybe (Item a, Item a)))
@cblp
cblp / ConIndex.hs
Created May 3, 2017 13:22
Get index of constructor in its type declaration.
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ScopedTypeVariables #-}
module ConIndex (conIndex) where
import Data.List (findIndex)
import Language.Haskell.TH (Con (..), Dec (DataD), ExpQ,
Info (DataConI, TyConI), Name, ParentName,
integerL, litE, reify)
#!/usr/bin/env stack
-- stack --resolver=lts-8.11 script --package=union
{-# OPTIONS -Wall -Werror #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE TypeApplications #-}
-- stack runhaskell
{-# OPTIONS -Wall -Werror #-}
{-# LANGUAGE LambdaCase #-}
import Control.Monad.State
import Data.IntMap
import Data.Woot
import Text.Show.Pretty
@cblp
cblp / First.hs
Created February 18, 2017 12:33
First as Applicative
{-# OPTIONS -Wall -Werror #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
import Control.Applicative ((<|>))
import Control.Monad (void)
import Test.QuickCheck
import Text.Show.Functions ()
{-# LANGUAGE LambdaCase #-}
import Data.Ratio (denominator, numerator)
data Expr = Number Rational | Paren Arith
instance Show Expr where
show = \case
Number n -> case denominator n of
1 -> show (numerator n)
_ -> show n
-- original code is written by https://github.com/klapaucius
{-# OPTIONS -Wall -Werror #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TypeFamilies #-}
module Main (main) where
@cblp
cblp / Deduction.hs
Last active July 19, 2016 12:59
"propositions as types" is cool!
module Logic.Deduction where
modusPonens :: (a -> b) -> a -> b
modusPonens = id
transitivity :: (b -> c) -> (a -> b) -> a -> c
transitivity = (.)
cons1 :: (a -> c) -> (b -> c) -> Either a b -> c
cons1 f _ (Left x) = f x
import System.IO.Unsafe
heavy y = unsafePerformIO $ do
putStrLn "heavy"
return y
f1 x = heavy 10 + x
f2 x = let y = heavy 10 in y + x