Skip to content

Instantly share code, notes, and snippets.

View saurabhnanda's full-sized avatar

Saurabh Nanda saurabhnanda

View GitHub Profile
Introduction
Welcome to our web development agency, where we specialize in crafting digital solutions tailored to meet your unique needs. At our agency, we understand the pivotal role that a well-designed website plays in today's digital landscape. Whether you're a small startup aiming to establish your online presence or a large corporation seeking to enhance user engagement, we have the expertise to turn your vision into reality. With a dedicated team of seasoned developers, designers, and strategists, we're committed to delivering top-notch products and services that exceed your expectations.
Custom Web Development
One of our core offerings is custom web development services. We recognize that every business is different, which is why we take a bespoke approach to each project. Our team works closely with you to understand your objectives, target audience, and brand identity. From there, we leverage the latest technologies and industry best practices to build a website that not only looks stunning but als
@saurabhnanda
saurabhnanda / Config.hs
Last active March 25, 2022 06:36
Comparitive code samples between Dhall and Haskell . Complete blog post at https://www.saurabhnanda.in/2022/03/24/dhall-a-gateway-drug-to-haskell/
-- Right at the very beginning, you have to deal with the mess of string types in Haskell.
{-# LANGUAGE OverloadedStrings #-}
module Config where
import Data.Aeson as Aeson
-- Union/sum type to decide the logging configuration
data LoggingCfg = LogFile String | Syslog
@saurabhnanda
saurabhnanda / Config.dhall
Last active June 6, 2022 21:16
Comparitive code samples between Dhall and Haskell. Complete blog post at https://www.saurabhnanda.in/2022/03/24/dhall-a-gateway-drug-to-haskell/
-- Union/sum type to decide the logging configuration
let LoggingCfg = < LogFile : Text | Syslog >
-- Configuration that is common across applications. One can also define
-- AppOneCfg and AppTwoCfg for config params that are specific to each app.
let CommonCfg =
{ logging : LoggingCfg
-- ^ the logging configuration that should be same across both applications
, topic : Text
let elmApps = [("File1.elm", "File1.js"), ("File2.elm", "File2.js")]
(buildDir </> "elm-apps.shake") %> \out -> do
srcFiles <- getDirectoryFiles "" ["elm-ui/src//*.elm"]
need ("elm-ui/elm-package.json":srcFiles)
forM_ elmApps $ \(elmSrc, outFile) -> do
cmd_ (Cwd "elm-ui") ["elm-make", "--output", "../dist" </> outFile, "--yes", "src" </> elmSrc]
cmd_ (Cwd "elm-ui") ["gulp", "checksum", "../dist"]
writeFile' out ""
streamly > /private/var/folders/j7/fgt692sj0wzg0lvrk86ctnxc0000gn/T/stack92624/streamly-0.7.1/src/Streamly/Internal/Data/Prim/Array/Types.hs:216:34: error:
streamly > • No instance for (Semigroup ByteArray) arising from a use of ‘<>’
streamly > • In the first argument of ‘byteArrayToPrimArray’, namely
streamly > ‘(primArrayToByteArray x <> primArrayToByteArray y)’
streamly > In the expression:
streamly > byteArrayToPrimArray
streamly > (primArrayToByteArray x <> primArrayToByteArray y)
streamly > In an equation for ‘<>’:
streamly > x <> y
streamly > = byteArrayToPrimArray
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module AppM where
import Control.Monad.Reader
import Models.BillingPlan hiding (StorefrontAccess, BackofficeAccess)
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE RankNTypes #-}
module Try2 where
import Control.Monad.Reader
data Permission = PermA | PermB | PermC deriving (Eq, Show)
data EnsurePermissions (ps :: [Permission]) = EnsurePermissions
instance ( HasServer api context
) => HasServer (EnsurePermissions (ps :: [Permission]) :> api) context where
type ServerT (EnsurePermissions ps :> api) m = (() -> ServerT api m)
-- I want to convert the type `ps` to it's equivalent value in this function
route Proxy context subserver = undefined
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
Apr 14 07:31:24 14333 kernel: [843556.475850] INFO: rcu_sched detected stalls on CPUs/tasks:
Apr 14 07:31:24 14333 kernel: [843556.475854] 0-...!: (1 GPs behind) idle=ffa/1/0 softirq=7326149/7326150 fqs=0
Apr 14 07:31:24 14333 kernel: [843556.475855] (detected by 1, t=34565 jiffies, g=5573741, c=5573740, q=262)
Apr 14 07:31:24 14333 kernel: [843556.475859] Sending NMI from CPU 1 to CPUs 0:
Apr 14 07:31:24 14333 kernel: [843556.476867] NMI backtrace for cpu 0
Apr 14 07:31:24 14333 kernel: [843556.476868] CPU: 0 PID: 0 Comm: swapper/0 Tainted: P O L 4.15.0-47-generic #50-Ubuntu
Apr 14 07:31:24 14333 kernel: [843556.476869] Hardware name: BHYVE, BIOS 1.00 03/14/2014
Apr 14 07:31:24 14333 kernel: [843556.476869] RIP: 0010:io_serial_in+0x18/0x20
Apr 14 07:31:24 14333 kernel: [843556.476869] RSP: 0018:ffff9b1a3fc03c10 EFLAGS: 00000002
Apr 14 07:31:24 14333 kernel: [843556.476870] RAX: 0000000084a02960 RBX: ffffffff85efee20 RCX: 0000000000000000