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 / atto.hs
Last active September 13, 2020 15:46
extract an enclosed subtext with attoparsec
import Control.Applicative ((<|>))
import Data.Attoparsec.Text hiding (match)
import Data.Text (Text)
atto :: Text -> Text -> Text -> Either String [Char]
atto x y = parseOnly $ untilWord x >> untilWord y
untilWord :: Text -> Parser [Char]
untilWord x = mempty <$ string x <|> (:) <$> anyChar <*> untilWord
@paolino
paolino / extract.hs
Last active September 13, 2020 14:59
extract an enclosed sublist
extract :: Eq a => [a] -> [a] -> [a] -> Maybe [a]
extract start end xs = do
ys <- snd <$> split start xs
fst <$> split end ys
split :: Eq a => [a] -> [a] -> Maybe ([a], [a])
split p = go id
where
go _ [] = Nothing
@paolino
paolino / divModIso.hs
Last active September 1, 2020 06:20
optics for things like div mods
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
import Control.Lens -- (over)
@paolino
paolino / curry record.hs
Last active August 27, 2020 07:59
how to apply a function on a record directly to its fields
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
-- needed for example
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-
dependencies:
- lens
- template-haskell
create all lenses for a record type preponing an l_ instead of removing the underscore
-}
import Control.Lens ((.~), lensRules, lensField, makeLensesWith, DefName(TopName), FieldNamer)
import Language.Haskell.TH (DecsQ, Name, nameBase, mkName)
{-
dependencies:
- lens
- template-haskell
create all lenses for a record type preponing an l_
-}
import Control.Lens ((.~), lensRules, lensField, makeLensesWith, DefName(TopName), FieldNamer)
import Language.Haskell.TH (DecsQ, Name, nameBase, mkName)
@paolino
paolino / ExpressiveShouldBe.hs
Last active August 19, 2020 16:51
pretty report inequality
{-
dependencies:
- base
- protolude
- tree-diff
-}
import Data.Typeable (Typeable)
import Data.TreeDiff (toExpr, exprDiff, ansiWlEditExpr, ToExpr)
import Text.Printf (printf)
@paolino
paolino / parse.hs
Created July 14, 2020 09:27
parse a list of different types driven by parser type
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
module Lib.Parse where
import Control.Lens (Getting, (^?), _Just)
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE NoImplicitPrelude #-}
@paolino
paolino / gmappend.hs
Created February 2, 2020 14:19
iso based gmappend for records
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}