Skip to content

Instantly share code, notes, and snippets.

View christian-marie's full-sized avatar

Christian Marie christian-marie

View GitHub Profile
-- | Our Union Find Map, this map takes the place of a sparse matrix in
-- implementing a very simple quick union (without weighting or path
-- compression).
type UFM = Map Tag Tag
-- | Find the partition root of a Tag.
findRoot :: Tag -> UFM -> Tag
findRoot tag m =
-- Chase pointers to the root of a partition, the end is signified by a
-- link to itself.
diff --git a/lib/Network/OAuth2/Server/App.hs b/lib/Network/OAuth2/Server/App.hs
index f93177f9b051..c60cca0573ff 100644
--- a/lib/Network/OAuth2/Server/App.hs
+++ b/lib/Network/OAuth2/Server/App.hs
@@ -58,6 +58,7 @@ import Control.Lens
import Control.Monad
import Control.Monad.IO.Class (MonadIO (liftIO))
import Control.Monad.Reader.Class (ask)
+import Data.ByteString.Char8 (readInt)
import Data.Either (lefts, rights)
from abc import ABCMeta, abstractmethod
from typing import TypeVar, Generic
T = TypeVar('T')
class IntAlg(Generic[T], metaclass=ABCMeta):
@abstractmethod
def lit(self, lit: int) -> T: pass
@abstractmethod
@christian-marie
christian-marie / Versions.hs
Created June 25, 2015 23:32
How we do servant versions at Anchor
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
-- | Description: API version in Servant requests.
module Servant.Anchor.Version where
20:27 < simon> does anyone have an example use of resource-pool?
20:28 < simon> and since I plan to use it with MySQL, should I be using the groundhog-mysql package?
20:32 < simon> wait, never mind about the last part. groundhog seems cool, but not sure I really want it right now.
20:44 < bitraten> simon: https://github.com/bitraten/bitrest/blob/master/src/Database.hs
20:47 < bitraten> In most cases you can ignore the IORef and just use a Reader
20:50 -!- rodlogic [~rodlogic@c-71-234-52-85.hsd1.ct.comcast.net] has quit [Remote host closed the connection]
21:00 < simon> bitraten, thanks!
21:10 < alpounet> simon: the simplest solution is probably to just make your Server a function that takes a 'Pool Connection' as argument
21:10 < alpounet> server :: Pool Connection -> Server YourAPI ; server pool = endpoint1 :<|> endpoint2 :<L> endpoint3 ...
21:11 < alpounet> and each request handler can use the pool
@christian-marie
christian-marie / gist:a92a26608599ae74adf4
Created March 26, 2015 01:23
GADTs for simple protocol
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as S
-- States
data Listening
data Disconnected
data Ready
{-# LANGUAGE OverloadedStrings #-}
import Data.Maybe
import OpenSSL.EVP.Sign
import OpenSSL.EVP.Verify
import OpenSSL.EVP.Digest
import OpenSSL.PEM
import OpenSSL
import Control.Applicative
main :: IO ()
@christian-marie
christian-marie / Makefile
Created December 16, 2014 23:48
Makefile for pandoc a4 pdfs
MARKDOWNS=$(wildcard *.md)
PDFS=$(MARKDOWNS:md=pdf)
all: $(PDFS)
clean:
rm -f $(PDFS)
%.pdf: %.md
pandoc -V geometry:margin=1in -V papersize:"a4paper" --toc $< -o $@
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
import Control.Applicative hiding ((<**>))
import Control.Lens
import Control.Monad
import Data.Aeson
diff -ru mlnx-ofa_kernel-2.3/drivers/infiniband/ulp/ipoib/ipoib.h mlnx-ofa_kernel-2.3p/drivers/infiniband/ulp/ipoib/ipoib.h
--- mlnx-ofa_kernel-2.3/drivers/infiniband/ulp/ipoib/ipoib.h 2014-11-06 22:18:12.000000000 +1100
+++ mlnx-ofa_kernel-2.3p/drivers/infiniband/ulp/ipoib/ipoib.h 2014-11-18 14:59:35.509774088 +1100
@@ -658,6 +658,8 @@
void ipoib_mcast_dev_down(struct net_device *dev);
void ipoib_mcast_dev_flush(struct net_device *dev);
+int ipoib_dma_map_tx(struct ib_device *ca, struct ipoib_tx_buf *tx_req);
+
#ifdef CONFIG_INFINIBAND_IPOIB_DEBUG