#StandAloneDerivatives
Explore tagged Tumblr posts
Text
youtube
Stand-Alone vs Embedded Derivatives Explained: CFA Level 1 by Sanjay Sir of SSEI
In this insightful podcast, Sanjay Sir breaks down the key differences between Stand-Alone Derivatives like call and put options, and Embedded Derivatives found within securities like bonds. Learn about Callable Bonds with built-in call options and Putable Bonds with put options, and how these embedded derivatives work in real-world financial instruments. This is an essential concept for CFA Level 1 candidates and anyone looking to deepen their understanding of derivatives. Don’t miss this clear and comprehensive explanation!
#StandAloneDerivatives#EmbeddedDerivatives#CFA#CFALevel1#SanjaySir#CallableBonds#PutableBonds#FinancialInstruments#DerivativesTrading#FinancePodcast#BondMarkets#SSEI#Youtube
0 notes
Text
Playing with Sigma, part 2
So we have Sigma now. What can we do with it?
{-# LANGUAGE DataKinds, GADTs, EmptyCase, InstanceSigs, OverloadedStrings, PolyKinds, ScopedTypeVariables, StandaloneDeriving, TemplateHaskell, TypeApplications, TypeFamilies, TypeOperators, UndecidableInstances #-} {-# OPTIONS_GHC -Wincomplete-patterns #-} import Data.Kind (Type) import Data.Singletons.Sigma import Data.Singletons.TH import Data.Text (Text) import qualified Data.Text as T singletons [d| data S = S1 | S2 | S3 | S4 deriving (Show, Eq) data T = T1 | T2 | T3 | T4 deriving (Show, Eq) |] data X (s :: S) where X1 :: X 'S1 X2 :: Int -> X 'S2 X3 :: Text -> X 'S3 X4 :: Float -> X 'S4 deriving instance Show (X s) data Y (t :: T) = Y Text deriving Show
First, you can wrap X in it, of course.
x1, x2, x3, x4 :: Sigma S (TyCon X) x1 = SS1 :&: X1 x2 = SS2 :&: X2 2 x3 = SS3 :&: X3 "3" x4 = SS4 :&: X4 4
Then, you can project the type and the value.
proj1 :: Sigma S t -> Text proj1 = projSigma1 f where f :: SS s -> Text f SS1 = "S1" f SS2 = "S2" f SS3 = "S3" f SS4 = "S4" proj2 :: Sigma S (TyCon X) -> Text proj2 = projSigma2 f where f :: X s -> Text f X1 = "X1" f (X2 n) = "X2 " T.pack (show n) f (X3 t) = "X3 " t f (X4 f) = "X4 " T.pack (show f)
And you can convert it to another Sigma using mapSigma. To use mapSigma, you need three functions; a type function, a function on singletons and a function on values. Let's try converting Sigma S (TyCon X) to Sigma T (TyCon Y).
First, you need a type function converting S to T.
type family Mf (s :: S ) :: T where Mf S1 = T1 Mf S2 = T2 Mf S3 = T3 Mf S4 = T4
Also, you need defunctionalization symbols for it.
data MfSym0 :: S ~> T type instance Apply MfSym0 s = Mf s
Second, you need a function on singletons.
sMf :: SS s -> ST (Mf s) sMf SS1 = ST1 sMf SS2 = ST2 sMf SS3 = ST3 sMf SS4 = ST4
Instead of writing all of them by hand, you can use singletons to generate them.
singletons [d| mf :: S -> T mf S1 = T1 mf S2 = T2 mf S3 = T3 mf S4 = T4 |]
Finally, you need a function on values.
mg :: X s -> Y t mg X1 = Y "X1" mg (X2 n) = Y $ "X2 " T.pack (show n) mg (X3 t) = Y $ "X3 " t mg (X4 f) = Y $ "X4 " T.pack (show f)
By combining them together, you can have a function converting Sigma S (TyCon X) to Sigma T (TyCon Y) using mapSigma.
m :: Sigma S (TyCon X) -> Sigma T (TyCon Y) m = mapSigma (SLambda sMf :: SLambda MfSym0) mg
0 notes
Text
Functions taking some types, part 2
In the previous post, we looked at how we can define functions taking some types with a phantom type. However, all of those functions need to know an actual type at the compile time. How can define functions that take some types which will be known at runtime?
First, let's pick a function from the previous post.
{-# LANGUAGE DataKinds, EmptyCase, GADTs, InstanceSigs, KindSignatures, LambdaCase, PolyKinds, ScopedTypeVariables, StandaloneDeriving, TemplateHaskell, TypeApplications, TypeFamilies, UndecidableInstances #-} {-# OPTIONS_GHC -Wincomplete-patterns #-} import Data.Kind (Type) import Data.Singletons.Decide (Decision(Proved, Disproved)) import Data.Singletons.TH import Data.Text (Text) import qualified Data.Text as T singletons [d| data S = S1 | S2 | S3 | S4 deriving (Show, Eq) |] data X :: S -> Type where X1 :: X 'S1 X2 :: Int -> X 'S2 X3 :: Text -> X 'S3 X4 :: Float -> X 'S4 deriving instance Show (X s) data F :: S -> Type where F2 :: F 'S2 F3 :: F 'S3 f :: F s -> X s -> Text f F2 (X2 n) = T.pack $ show n f F3 (X3 t) = t
This function takes a witness saying s is one of 'S2 or 'S3 (F s) and actual value (X s), and was named f3 in the previous post. We'll see how we can call this function from functions that don't know the parameter type at the compile time.
Now, let's define SomeX. This type has X s in it, but indexes it by Sing s. This type represents X whose actual type is unknown until runtime.
data SomeX where SomeX :: Sing s -> X s -> SomeX
The first example is pattern-matching Sing s in Some X. Since s in Sing s and X s are unified, the compiler can know which type X s is.
f1 :: SomeX -> Maybe Text f1 (SomeX SS1 _) = Nothing f1 (SomeX SS2 x) = Just $ f F2 x f1 (SomeX SS3 x) = Just $ f F3 x f1 (SomeX SS4 _) = Nothing c1 :: Maybe Text c1 = f1 $ SomeX SS2 $ X2 2
This is pretty straightforward, but there is one problem. Imagine you've updated F and f to accept X 'S4 like this, but you forgot updating f1.
data F :: S -> Type where F2 :: F 'S2 F3 :: F 'S3 F4 :: F 'S4 f :: F s -> X s -> Text f F2 (X2 n) = T.pack $ show n f F3 (X3 t) = t f F4 (X4 f) = T.pack $ show f
Even though f accepts X 'S4, f1 still returns Nothing. And the compiler never tells you about it. What can we do?
It's time to take advantage of Decision from Data.Singletons.Decicde. Let's define isF which tells your compiler which s it can use with F.
isF :: Sing s -> Decision (F s) isF SS1 = Disproved $ \case {} isF SS2 = Proved F2 isF SS3 = Proved F3 isF SS4 = Disproved $ \case {}
The cases in Disproved for SS1 and SS4 are empty because there are no patterns matching it. In these cases, the compiler knows that it's pattern-matching against F 'S1 and F 'S4, but there are no such values in F.
You can define f2 using this isF this way.
f2 :: SomeX -> Maybe Text f2 (SomeX s x) | Proved p <- isF s = Just $ f p x | otherwise = Nothing c2 :: Maybe Text c2 = f2 $ SomeX SS2 $ X2 2
So what happens when you change F and f to accept X 'S4? GHC tells you the pattern is non-exhaustive.
paramdynamic.hs:65:23: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In a case alternative: Patterns not matched: F4 | 65 | isF SS4 = Disproved $ \case {} | ^^^^^^^^
This is because the compiler knows there is a value of F 'S4 now. Writing f2 is bit complicated than f1, but the compiler will give you some sort of safety if you do so.
0 notes
Text
Functions taking some types, part 1
Imagine you have type X indexed by a phantom type S.
{-# LANGUAGE DataKinds, EmptyCase, FlexibleContexts, GADTs, InstanceSigs, MultiParamTypeClasses, PolyKinds, ScopedTypeVariables, StandaloneDeriving, TemplateHaskell, TypeApplications, TypeFamilies, UndecidableInstances #-} {-# OPTIONS_GHC -Wincomplete-patterns #-} import Data.Kind ( Constraint , Type ) import Data.Singletons.Prelude ( Elem , If ) import Data.Singletons.TH import Data.Text (Text) import qualified Data.Text as T singletons [d| data S = S1 | S2 | S3 | S4 deriving (Show, Eq) |] data X :: S -> Type where X1 :: X 'S1 X2 :: Int -> X 'S2 X3 :: Text -> X 'S3 X4 :: Float -> X 'S4 deriving instance Show (X s)
You want to define a function taking X with some of S. For example, that function takes X 'S2 and X 'S3, but doesn't take X 'S1 nor X 'S4. How do you write this function?
The simplest approach would be to use Either. Your function will take Either (X 'S2) (X 'S3).
f1 :: Either (X 'S2) (X 'S3) -> Text f1 (Left (X2 n)) = T.pack $ show n f1 (Right (X3 t)) = t
You can call it by wrapping your X by Left or Right.
c1 :: Text c1 = f1 $ Left $ X2 2
This is pretty straightforward, but you need to nest Either when you make this function take X 'S4 too, which is a bit annoying.
How about using a constraint? You can define a type function (type family) of kind S -> Constraint and use it as a constraint of the function.
type family F2 s :: Constraint where F2 'S2 = () F2 'S3 = () F2 _ = ('True ~ 'False) f2 :: F2 s => X s -> Text f2 (X2 n) = T.pack $ show n f2 (X3 t) = t c2 :: Text c2 = f2 $ X2 2
As you know, applying a type constraint to a function is the same thing as passing a table explicitly. You'll define a GADT of kind S -> Type (instead of defining a type constraint of kind S -> Constraint) to do this.
data F3 :: S -> Type where F32 :: F3 'S2 F33 :: F3 'S3 f3 :: F3 s -> X s -> Text f3 F32 (X2 n) = T.pack $ show n f3 F33 (X3 t) = t c3 :: Text c3 = f3 F32 $ X2 2
In this approach, you need to pass F3 explicitly to f3 whereas it was implicitly passed to f2. Can we make it implicit? Yes, first, let's define Proved type class.
class Proved p a where auto :: p a
Then, make F3 instances of this class.
instance Proved F3 'S2 where auto = F32 instance Proved F3 'S3 where auto = F33
Then, you can always pass auto as its first parameter and the complier will find a proper instance.
f3' :: Proved F3 s => X s -> Text f3' = f3 auto c3' :: Text c3' = f3' $ X2 2
f3' is a bit generic version of f2 but they do the same thing.
If you think it's cumbersome to write F2 or F3, you could make a type of the function take a list of types directly by writing a helper constraint OneOf.
type family OneOf t l :: Constraint where OneOf t l = If (Elem t l) (() :: Constraint) ('True ~ 'False) f4 :: OneOf s '[ 'S2, 'S3 ] => X s -> Text f4 (X2 n) = T.pack $ show n f4 (X3 t) = t c4 :: Text c4 = f4 $ X2 2
0 notes
Text
Why you need singletons?
Imagine you have a type Value indexed by ValType kind, and an existential type SomeValue that wraps it.
{-# LANGUAGE AllowAmbiguousTypes, DataKinds, GADTs, KindSignatures, ScopedTypeVariables, StandaloneDeriving, TypeApplications #-} import Data.Text (Text) data ValType = Text | Bool data Value (tag :: ValType) where T :: Text -> Value 'Text B :: Bool -> Value 'Bool deriving instance Show (Value tag) data SomeValue = forall tag. SomeValue (Value tag)
Now, you want to have a function that unwraps a Value from a SomeValue. This can be done by using singletons.
data SValType (tag :: ValType) where SText :: SValType 'Text SBool :: SValType 'Bool class SValTypeI (tag :: ValType) where sing :: SValType tag instance SValTypeI 'Text where sing = SText instance SValTypeI 'Bool where sing = SBool unwrap :: forall tag. SValTypeI tag => SomeValue -> Maybe (Value tag) unwrap (SomeValue v) = case sing @tag of SBool | B _ Just v SText | T _ Just v _ -> Nothing
But doesn't this look redundant? Why can't you get a ValueType directly instead of getting SValType like this?
class IsType (a :: ValType) where typeOf :: ValType instance IsType 'Text where typeOf = Text instance IsType 'Bool where typeOf = Bool unwarp' :: forall tag. IsType tag => SomeValue -> Maybe (Value tag) unwarp' (SomeValue v) = case typeOf @tag of Bool | B _ Just v Text | T _ Just v _ -> Nothing
But no, this doesn't compile. But why?
You can think about this in this way. Passing a typeclass to a function is identical to passing a dictionary of functions to the function. So this unwrap' is identical to this definition because IsType only has typeOf that returns ValType.
unwarpExplicit' :: ValType -> SomeValue -> Maybe (Value tag) unwarpExplicit' valType (SomeValue v) = case valType of Bool | B _ Just v Text | T _ Just v _ -> Nothing
But as you can see, there are no relationships between ValType and tag. That's why this doesn't compile. valueType being Bool doesn't mean tag is 'Bool, and you cannot pattern match v with B _.
On the other hand, it'll become this when you convert the original wrap to pass a dictionary explicitly.
unwrapExplicit :: SValType tag -> SomeValue -> Maybe (Value tag) unwrapExplicit sValType (SomeValue v) = case sValType of SBool | B _ Just v SText | T _ Just v _ -> Nothing
As you can see, SValType tag has tag which will be unified with tag in Maybe (Value tag). When you specify a return type of this function, you also fix sValType. For example, unwrapExplicit SBool (SomeValue (B False)) :: Maybe (Value 'Bool) compiles, but unwrapExplicit SText (SomeValue (B False)) :: Maybe (Value 'Bool) doesn't.
If sValueType is SBool, the return type must be Maybe (Value 'Bool), and if SText, it must be Maybe (Value 'Text). This makes it possible to pattern match on v with B _ and T _.
0 notes
Text
Calculating fibonacci numbers using recursion schemes
After reading the good articles about recursion scheme by Patrick Thomson, I tried the example in Recursion Schemes, Part IV: Time is of the Essence to calculate fibonacci numbers using histomorphism.
First, let's define histo function. I just took these definitions from those articles.
{-# LANGUAGE DeriveFunctor, StandaloneDeriving, UndecidableInstances #-} import Control.Arrow ((>>>), (<<<), (&&&)) newtype Term f = In { out :: f (Term f) } deriving instance Show (f (Term f)) => Show (Term f) type Coalgebra f a = a -> f a ana :: (Functor f) => Coalgebra f a -> a -> Term f ana coalg = In <<< fmap (ana coalg) <<< coalg data Attr f a = Attr { attribute :: a , hole :: f (Attr f a) } type CVAlgebra f a = f (Attr f a) -> a histo :: Functor f => CVAlgebra f a -> Term f -> a histo h = worker >>> attribute where worker = out >>> fmap worker >>> (h &&& id) >>> uncurry Attr
Now, you need a number type defined using recursions.
data NatF a = ZeroF | SuccF a deriving (Show, Functor) type Nat = Term NatF
You can generate a number of Nat from an ordinal number by using ana.
nat :: (Eq n, Num n) => n -> Nat nat n = ana build n where build 0 = ZeroF build n = SuccF (n - 1)
Then, what you need to do is to write a function that calculates a fibonacci number from NatF (Attr NatF a).
fibF :: Num n => NatF (Attr NatF n) -> n fibF ZeroF = 0 fibF (SuccF (Attr a ZeroF)) = 1 fibF (SuccF (Attr a (SuccF (Attr b _)))) = a + b
As you can see, you pick the previous fibonacci number directly and pick the previous previous fibonacci number from the history in the last pattern.
You can now calculate a fibonacci number by passing fibF to histo.
fib :: (Eq n, Num n, Num m) => n -> m fib n = histo fibF $ nat n
When you compare this fib with this naive implementation (fib'), you'll find that fib runs significantly faster than fib' because it caches intermediate fibonacci numbers.
fib' :: (Eq n, Num n) => n -> n fib' 0 = 0 fib' 1 = 1 fib' n = fib' (n - 1) + fib' (n - 2)
By the way, you don't need to write most of the code above when you use recursion-schemes. As described in Recursion Schemes, Part 4½: Better Living Through Base Functors, it provides a base functor for GHC.Natural.Natural (it's Maybe because our NatF is isomorphic to Maybe), and lifts Natural to Maybe automatically. Also it uses Control.Comonad.Cofree instead of our Attr.
So what you need to do is just write fibF for it.
{-# LANGUAGE TypeApplications #-} import Control.Comonad.Cofree (Cofree((:<))) import Data.Functor.Foldable (Base, histo) import GHC.Natural (Natural) fibF :: Num n => (Base Natural) (Cofree (Base Natural) n) -> n fibF Nothing = 0 fibF (Just (a :< Nothing)) = 1 fibF (Just (a :< Just (b :< _))) = a + b fib :: (Integral n, Num m) => n -> m fib n = histo fibF $ fromIntegral @_ @Natural n
0 notes