Skip to content

Instantly share code, notes, and snippets.

View Lev135's full-sized avatar
📚
Studying mathematics

Lev Dvorkin Lev135

📚
Studying mathematics
  • 18:25 (UTC +03:00)
View GitHub Profile
@Lev135
Lev135 / Main.hs
Created June 28, 2022 16:38
Unordered applicative
{-# LANGUAGE ApplicativeDo #-}
module Main where
import Data.Void (Void)
import Text.Megaparsec (Parsec, parseTest)
import Text.Megaparsec.Char (char)
import Text.Megaparsec.Char.Lexer (decimal)
import UnordApp (liftApp, runUnord)
@Lev135
Lev135 / LookAhead.hs
Created July 20, 2022 12:59
Check if every list composed from the set of patterns can be uniquely decomposed into patterns using Sardinas-Peterson's algorithm
module LookAhead
( Pattern (..),
ConflictPatterns,
checkUniquePatSplit,
checkUniquePatSplit',
)
where
import Control.Monad (guard, when)
import Data.Bifunctor (Bifunctor (..))
@Lev135
Lev135 / Main.hs
Created July 25, 2022 19:10
Debugging megaparsec transofrmer using `MonadParsecDbg` class
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
-- | This module contains usage example of suggested `MonadParsecDbg` type class,
-- minimized, but, I hope, demonstrative
--
-- If someone have better solution, I would like to see it
module Main where
@Lev135
Lev135 / Main.hs
Created August 5, 2022 07:28
'mtl' classes with mappable errors
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE PartialTypeSignatures #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wall #-}
{-# OPTIONS_GHC -Wno-partial-type-signatures #-}
@Lev135
Lev135 / Calc.hs
Created October 31, 2022 19:42
Wrapper for evaluation, that can be reordered for efficiency
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TupleSections #-}
module Calc (
Calc, call, runCalc, runCalcM, extractCalls,
runCalcSortBy, runCalcSortOn, runCalcSort,
contramapRes, mapInit, traverseInit
) where
@Lev135
Lev135 / Main.hs
Last active June 4, 2023 20:14
Eval by need (with named varriables)
module Main where
import Data.Either.Extra (maybeToEither)
data Expr
= Var String
| Lam String Expr
| App Expr Expr
| Lit Int
| Prim PrimOp Expr Expr
@Lev135
Lev135 / Main.hs
Last active June 4, 2023 21:07
Call by name?
module Main where
import Data.Maybe (fromJust)
data Expr
= Var String
| Lam String Expr
| App Expr Expr
| Lit Int
| Prim PrimOp Expr Expr
| Let (String, Expr) Expr
@Lev135
Lev135 / MLens.hs
Created June 9, 2023 12:24
Effectful composible lens
import Control.Monad ((>=>))
import Data.Map (Map)
import qualified Data.Map as M
import GHC.Generics (Generic)
import Optics
data MLens m s a = MLens
{ mview :: s -> m a
, mset :: a -> s -> m s
}
@Lev135
Lev135 / LensM.hs
Last active June 10, 2023 00:12
Monadic lens in Van Laarhoven representation
{-# LANGUAGE RankNTypes #-}
module LensM where
import Control.Applicative (Const(..))
import Data.Functor.Identity (Identity(..))
import Data.Functor.Contravariant (Contravariant)
import Data.Functor.Compose
class Functor f => MfaAms f where
@Lev135
Lev135 / monadic-lens.md
Created June 10, 2023 22:39
Monadic variants of optics from Haskell lens library

Monadic lens

So much has been written about lens and other optics in Haskell that these ideas are likely not very original. However, I'll try.

Initial problem

Let's say we have some recursive data type:

type Record = Map String Value
data Value = I Int | R Record
  deriving (Generic, Show)