Skip to content

Instantly share code, notes, and snippets.

View paolino's full-sized avatar

Paolo Veronelli paolino

  • Cardano Foundation
  • albufeira, portugal
View GitHub Profile
@paolino
paolino / expression_problem.hs
Last active March 16, 2024 00:52
Haskell with the expression problems
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
@paolino
paolino / partial_replace.hs
Last active February 25, 2024 15:41
a replace that streams
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE OverloadedStrings #-}
import Prelude
import Data.Functor (Identity (runIdentity))
import Control.Monad.Fix (fix)
import Data.Bifunctor (Bifunctor (..), second)
import Data.List (tails)
@paolino
paolino / replace.hs
Last active February 24, 2024 20:46
replace all occurencies of a string
import Data.List (tails)
import Data.List.NonEmpty (NonEmpty, toList)
import Prelude
import qualified Data.List.NonEmpty as NE
type Tries = [NonEmpty Char]
tries :: String -> Tries
tries [] = []
@paolino
paolino / mgerqoirg.txt
Last active February 21, 2024 22:30
ford johnson no recursion
-- input
mgerqoirg
------------------------------------
--> step 0 : create board with couples
----- board ----------
m..rq..r. -- unordered
g eo ig
@paolino
paolino / NamedRecords.hs
Last active November 26, 2023 19:11
Cassava instances via Generics.SOP
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
@paolino
paolino / Arith.hs
Last active November 12, 2023 10:54
Evaluator of arithmetic expressions
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE LambdaCase #-}
-- do not import other stuff here
import Control.Applicative
( Alternative (empty, (<|>))
, many
)
import Control.Monad (forever)
import Data.Char (ord)
@paolino
paolino / Parser.hs
Last active November 11, 2023 19:32
Arithmetic expression parser
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE LambdaCase #-}
module Arith where
-- do not import other stuff here
import Control.Applicative
( Alternative (empty, (<|>))
, many
@paolino
paolino / optparse.hs
Created September 13, 2023 15:49
A famous applicative
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
import Data.String (IsString)
@paolino
paolino / changeBrute.hs
Last active November 13, 2022 19:11
counting coins, brute force
module Change () where
import Data.List (sortOn)
import Data.Ord (Down(..))
import Control.Exception.Base (assert)
-- count the number of ways a `tot` can be realized using the given coins
-- any coin can be used any number of times
countChangeOpen :: Int -> [Int] -> Int
countChangeOpen tot coins = consumeOpen tot $ sortOn Down coins
@paolino
paolino / counting.hs
Last active November 12, 2022 18:56
Counting problem, unpruned
{-# OPTIONS_GHC -Wno-unused-top-binds #-}
module Counting () where
-- some values
type S a = [a]
-- any combining operation between 2 values (+, - , * ...)
type Op a = a -> a -> a