Skip to content

Instantly share code, notes, and snippets.

View paolino's full-sized avatar

Paolo Veronelli paolino

  • Cardano Foundation
  • sesimbra, portugal
View GitHub Profile

Oracles

An oracle is a push-based off-chain system that observes GitHub's state and publishes an attestation of the observed information on-chain.

Users must trigger the sampling process by providing the oracle the expected value to be attested. This approach prevents oversampling of GitHub and ensures the oracle is directly compensated for its service.

Oracles serve as information sources referenced in vetting minting

@paolino
paolino / ByteStringCalculator.hs
Created May 22, 2024 09:58
An exercise to learn a bit of type level programming in the style of Servant with kinds
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
@paolino
paolino / ByteStringCalculator.hs
Last active May 20, 2024 16:35
An exercise to learn a bit of type level programming in the style of Servant
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
@paolino
paolino / PullPush.hs
Last active May 22, 2024 10:01
Push to pull transformation, from push callbacks to pull streaming, with generics
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeApplications #-}
@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)